New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90

    • Property svn:keywords set to Id
    r3614 r6225  
    1212   !!            -    !                            Currently needs a fixed processor 
    1313   !!            -    !                            layout between restarts 
     14   !!            -    !  2015-11  Dave Storkey     Convert icb_rst_read to use IOM so can 
     15   !!                                              read single restart files 
    1416   !!---------------------------------------------------------------------- 
    1517   !!---------------------------------------------------------------------- 
     
    2224   USE lib_mpp        ! NEMO MPI library, lk_mpp in particular 
    2325   USE netcdf         ! netcdf routines for IO 
     26   USE iom 
    2427   USE icb_oce        ! define iceberg arrays 
    2528   USE icbutl         ! iceberg utility routines 
     
    4245   !!---------------------------------------------------------------------- 
    4346   !! NEMO/OPA 3.3 , NEMO Consortium (2011) 
    44    !! $Id:$ 
     47   !! $Id$ 
    4548   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    4649   !!---------------------------------------------------------------------- 
     
    5760      INTEGER                      ::   idim, ivar, iatt 
    5861      INTEGER                      ::   jn, iunlim_dim, ibergs_in_file 
    59       INTEGER                      ::   iclass 
    60       INTEGER, DIMENSION(1)        ::   istrt, ilngth, idata 
    61       INTEGER, DIMENSION(2)        ::   istrt2, ilngth2 
    62       INTEGER, DIMENSION(nkounts)  ::   idata2 
    63       REAL(wp), DIMENSION(1)       ::   zdata                                         ! need 1d array to read in with 
    64                                                                                             ! start and count arrays 
     62      INTEGER                      ::   ii,ij,iclass 
     63      REAL(wp), DIMENSION(nkounts) ::   zdata       
    6564      LOGICAL                      ::   ll_found_restart 
    66       CHARACTER(len=80)            ::   cl_filename 
     65      CHARACTER(len=256)           ::   cl_path 
     66      CHARACTER(len=256)           ::   cl_filename 
    6767      CHARACTER(len=NF90_MAX_NAME) ::   cl_dname 
    6868      TYPE(iceberg)                ::   localberg ! NOT a pointer but an actual local variable 
     
    7070      !!---------------------------------------------------------------------- 
    7171 
    72       ! Find a restart file 
    73       cl_filename = ' ' 
    74       IF ( lk_mpp ) THEN 
    75          cl_filename = ' ' 
    76          WRITE( cl_filename, '("restart_icebergs_",I4.4,".nc")' ) narea-1 
    77          INQUIRE( file=TRIM(cl_filename), exist=ll_found_restart ) 
    78       ELSE 
    79          cl_filename = 'restart_icebergs.nc' 
    80          INQUIRE( file=TRIM(cl_filename), exist=ll_found_restart ) 
    81       ENDIF 
    82  
    83       IF ( .NOT. ll_found_restart) THEN                     ! only do the following if a file was found 
    84          CALL ctl_stop('icebergs: no restart file found') 
    85       ENDIF 
    86  
    87       IF (nn_verbose_level >= 0 .AND. lwp)  & 
    88          WRITE(numout,'(2a)') 'icebergs, read_restart_bergs: found restart file = ',TRIM(cl_filename) 
    89  
    90       nret = NF90_OPEN(TRIM(cl_filename), NF90_NOWRITE, ncid) 
    91       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_open failed') 
    92  
    93       nret = nf90_inquire(ncid, idim, ivar, iatt, iunlim_dim) 
    94       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inquire failed') 
    95  
    96       IF( iunlim_dim .NE. -1) THEN 
    97  
    98          nret = nf90_inquire_dimension(ncid, iunlim_dim, cl_dname, ibergs_in_file) 
    99          IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inq_dimlen failed') 
    100  
    101          nret = NF90_INQ_VARID(ncid, 'number', numberid) 
    102          nret = NF90_INQ_VARID(ncid, 'mass_scaling', nscaling_id) 
    103          nret = NF90_INQ_VARID(ncid, 'xi', nxid) 
    104          nret = NF90_INQ_VARID(ncid, 'yj', nyid) 
    105          nret = NF90_INQ_VARID(ncid, 'lon', nlonid) 
    106          nret = NF90_INQ_VARID(ncid, 'lat', nlatid) 
    107          nret = NF90_INQ_VARID(ncid, 'uvel', nuvelid) 
    108          nret = NF90_INQ_VARID(ncid, 'vvel', nvvelid) 
    109          nret = NF90_INQ_VARID(ncid, 'mass', nmassid) 
    110          nret = NF90_INQ_VARID(ncid, 'thickness', nthicknessid) 
    111          nret = NF90_INQ_VARID(ncid, 'width', nwidthid) 
    112          nret = NF90_INQ_VARID(ncid, 'length', nlengthid) 
    113          nret = NF90_INQ_VARID(ncid, 'year', nyearid) 
    114          nret = NF90_INQ_VARID(ncid, 'day', ndayid) 
    115          nret = NF90_INQ_VARID(ncid, 'mass_of_bits', nmass_of_bits_id) 
    116          nret = NF90_INQ_VARID(ncid, 'heat_density', nheat_density_id) 
    117  
    118          ilngth(1) = 1 
    119          istrt2(1) = 1 
    120          ilngth2(1) = nkounts 
    121          ilngth2(2) = 1 
    122          DO jn=1, ibergs_in_file 
    123  
    124             istrt(1) = jn 
    125             istrt2(2) = jn 
    126  
    127             nret = NF90_GET_VAR(ncid, numberid, idata2, istrt2, ilngth2 ) 
    128             localberg%number(:) = idata2(:) 
    129  
    130             nret = NF90_GET_VAR(ncid, nscaling_id, zdata, istrt, ilngth ) 
    131             localberg%mass_scaling = zdata(1) 
    132  
    133             nret = NF90_GET_VAR(ncid, nlonid, zdata, istrt, ilngth) 
    134             localpt%lon = zdata(1) 
    135             nret = NF90_GET_VAR(ncid, nlatid, zdata, istrt, ilngth) 
    136             localpt%lat = zdata(1) 
    137             IF (nn_verbose_level >= 2 .AND. lwp) THEN 
    138                WRITE(numout,'(a,i5,a,2f10.4,a,i5)') 'icebergs, read_restart_bergs: berg ',jn,' is at ', & 
    139                                               localpt%lon,localpt%lat,' on PE ',narea-1 
     72      ! Find a restart file. Assume iceberg restarts in same directory as ocean restarts 
     73      ! and are called TRIM(cn_ocerst)//'_icebergs' 
     74      cl_path = TRIM(cn_ocerst_indir) 
     75      IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/' 
     76      cl_filename = TRIM(cn_ocerst_in)//'_icebergs' 
     77      CALL iom_open( TRIM(cl_path)//cl_filename, ncid ) 
     78 
     79      IF( iom_file(ncid)%iduld .GE. 0) THEN 
     80 
     81         ibergs_in_file = iom_file(ncid)%lenuld 
     82         DO jn = 1,ibergs_in_file 
     83 
     84            ! iom_get treats the unlimited dimension as time. Here the unlimited dimension  
     85            ! is the iceberg index, but we can still use the ktime keyword to get the iceberg we want.  
     86 
     87            CALL iom_get( ncid, 'xi'     ,localpt%xi  , ktime=jn ) 
     88            CALL iom_get( ncid, 'yj'     ,localpt%yj  , ktime=jn ) 
     89 
     90            ii = INT( localpt%xi + 0.5 ) 
     91            ij = INT( localpt%yj + 0.5 ) 
     92            ! Only proceed if this iceberg is on the local processor (excluding halos). 
     93            IF ( ii .GE. nldi+nimpp-1 .AND. ii .LE. nlei+nimpp-1 .AND. & 
     94           &     ij .GE. nldj+njmpp-1 .AND. ij .LE. nlej+njmpp-1 ) THEN            
     95 
     96               CALL iom_get( ncid, jpdom_unknown, 'number'       , zdata(:) , ktime=jn, kstart=(/1/), kcount=(/nkounts/) ) 
     97               localberg%number(:) = INT(zdata(:)) 
     98               CALL iom_get( ncid, 'mass_scaling' , localberg%mass_scaling, ktime=jn ) 
     99               CALL iom_get( ncid, 'lon'          , localpt%lon           , ktime=jn ) 
     100               CALL iom_get( ncid, 'lat'          , localpt%lat           , ktime=jn ) 
     101               CALL iom_get( ncid, 'uvel'         , localpt%uvel          , ktime=jn ) 
     102               CALL iom_get( ncid, 'vvel'         , localpt%vvel          , ktime=jn ) 
     103               CALL iom_get( ncid, 'mass'         , localpt%mass          , ktime=jn ) 
     104               CALL iom_get( ncid, 'thickness'    , localpt%thickness     , ktime=jn ) 
     105               CALL iom_get( ncid, 'width'        , localpt%width         , ktime=jn ) 
     106               CALL iom_get( ncid, 'length'       , localpt%length        , ktime=jn ) 
     107               CALL iom_get( ncid, 'year'         , zdata(1)              , ktime=jn ) 
     108               localpt%year = INT(zdata(1)) 
     109               CALL iom_get( ncid, 'day'          , localpt%day           , ktime=jn ) 
     110               CALL iom_get( ncid, 'mass_of_bits' , localpt%mass_of_bits  , ktime=jn ) 
     111               CALL iom_get( ncid, 'heat_density' , localpt%heat_density  , ktime=jn ) 
     112 
     113               ! 
     114               CALL icb_utl_add( localberg, localpt ) 
     115 
    140116            ENDIF 
    141             nret = NF90_GET_VAR(ncid, nxid, zdata, istrt, ilngth) 
    142             localpt%xi = zdata(1) 
    143             nret = NF90_GET_VAR(ncid, nyid, zdata, istrt, ilngth) 
    144             localpt%yj = zdata(1) 
    145             nret = NF90_GET_VAR(ncid, nuvelid, zdata, istrt, ilngth ) 
    146             localpt%uvel = zdata(1) 
    147             nret = NF90_GET_VAR(ncid, nvvelid, zdata, istrt, ilngth ) 
    148             localpt%vvel = zdata(1) 
    149             nret = NF90_GET_VAR(ncid, nmassid, zdata, istrt, ilngth ) 
    150             localpt%mass = zdata(1) 
    151             nret = NF90_GET_VAR(ncid, nthicknessid, zdata, istrt, ilngth ) 
    152             localpt%thickness = zdata(1) 
    153             nret = NF90_GET_VAR(ncid, nwidthid, zdata, istrt, ilngth ) 
    154             localpt%width = zdata(1) 
    155             nret = NF90_GET_VAR(ncid, nlengthid, zdata, istrt, ilngth ) 
    156             localpt%length = zdata(1) 
    157             nret = NF90_GET_VAR(ncid, nyearid, idata, istrt, ilngth ) 
    158             localpt%year = idata(1) 
    159             nret = NF90_GET_VAR(ncid, ndayid, zdata, istrt, ilngth ) 
    160             localpt%day = zdata(1) 
    161             nret = NF90_GET_VAR(ncid, nmass_of_bits_id, zdata, istrt, ilngth ) 
    162             localpt%mass_of_bits = zdata(1) 
    163             nret = NF90_GET_VAR(ncid, nheat_density_id, zdata, istrt, ilngth ) 
    164             localpt%heat_density = zdata(1) 
    165             ! 
    166             CALL icb_utl_add( localberg, localpt ) 
     117 
    167118         END DO 
    168          ! 
    169       ENDIF 
    170  
    171       nret = NF90_INQ_DIMID( ncid, 'c', nc_dim ) 
    172       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inq_dimid c failed') 
    173  
    174       nret = NF90_INQUIRE_DIMENSION( ncid, nc_dim, cl_dname, iclass ) 
    175       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inquire_dimension failed') 
    176  
    177       nret = NF90_INQ_VARID(ncid, 'kount'       , nkountid) 
    178       nret = NF90_INQ_VARID(ncid, 'calving'     , ncalvid) 
    179       nret = NF90_INQ_VARID(ncid, 'calving_hflx', ncalvhid) 
    180       nret = NF90_INQ_VARID(ncid, 'stored_ice'  , nsiceid) 
    181       nret = NF90_INQ_VARID(ncid, 'stored_heat' , nsheatid) 
    182  
    183       nstrt3(1) = 1 
    184       nstrt3(2) = 1 
    185       nlngth3(1) = jpi 
    186       nlngth3(2) = jpj 
    187       nlngth3(3) = 1 
    188  
    189       DO jn = 1, iclass 
    190          nstrt3(3) = jn 
    191          nret      = NF90_GET_VAR( ncid, nsiceid , griddata, nstrt3, nlngth3 ) 
    192          berg_grid%stored_ice(:,:,jn) = griddata(:,:,1) 
    193       END DO 
    194  
    195       nret = NF90_GET_VAR( ncid, ncalvid , src_calving          (:,:) ) 
    196       nret = NF90_GET_VAR( ncid, ncalvhid, src_calving_hflx     (:,:) ) 
    197       nret = NF90_GET_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
    198       nret = NF90_GET_VAR( ncid, nkountid, idata2(:) ) 
    199       num_bergs(:) = idata2(:) 
    200  
    201       ! Finish up 
    202       nret = NF90_CLOSE(ncid) 
    203       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_close failed') 
     119 
     120      ENDIF  
     121 
     122      ! Gridded variables 
     123      CALL iom_get( ncid, jpdom_autoglo,    'calving'     , src_calving  ) 
     124      CALL iom_get( ncid, jpdom_autoglo,    'calving_hflx', src_calving_hflx  ) 
     125      CALL iom_get( ncid, jpdom_autoglo,    'stored_heat' , berg_grid%stored_heat  ) 
     126      CALL iom_get( ncid, jpdom_autoglo_xy, 'stored_ice'  , berg_grid%stored_ice, kstart=(/1,1,1/), kcount=(/1,1,nclasses/) ) 
     127       
     128      CALL iom_get( ncid, jpdom_unknown, 'kount' , zdata(:) ) 
     129      num_bergs(:) = INT(zdata(:)) 
    204130 
    205131      ! Sanity check 
     
    208134         WRITE(numout,'(2(a,i5))') 'icebergs, read_restart_bergs: # bergs =',jn,' on PE',narea-1 
    209135      IF( lk_mpp ) THEN 
    210          CALL mpp_sum(ibergs_in_file) 
     136         ! Only mpp_sum ibergs_in_file if we are reading from multiple restart files.  
     137         IF( INDEX(iom_file(ncid)%name,'icebergs.nc' ) .EQ. 0 ) CALL mpp_sum(ibergs_in_file) 
    211138         CALL mpp_sum(jn) 
    212139      ENDIF 
     
    214141         &                                    ' bergs in the restart file and', jn,' bergs have been read' 
    215142      ! 
     143      ! Finish up 
     144      CALL iom_close( ncid ) 
     145      ! 
    216146      IF( lwp .and. nn_verbose_level >= 0)  WRITE(numout,'(a)') 'icebergs, read_restart_bergs: completed' 
    217147      ! 
     
    228158      INTEGER ::   jn   ! dummy loop index 
    229159      INTEGER ::   ix_dim, iy_dim, ik_dim, in_dim 
    230       CHARACTER(len=80)      :: cl_filename 
     160      CHARACTER(len=256)     :: cl_path 
     161      CHARACTER(len=256)     :: cl_filename 
    231162      TYPE(iceberg), POINTER :: this 
    232163      TYPE(point)  , POINTER :: pt 
    233164      !!---------------------------------------------------------------------- 
    234165 
     166      ! Assume we write iceberg restarts to same directory as ocean restarts. 
     167      cl_path = TRIM(cn_ocerst_outdir) 
     168      IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/' 
    235169      IF( lk_mpp ) THEN 
    236          WRITE(cl_filename,'("icebergs_",I8.8,"_restart_",I4.4,".nc")') kt, narea-1 
     170         WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart_",I4.4,".nc")') TRIM(cexper), kt, narea-1 
    237171      ELSE 
    238          WRITE(cl_filename,'("icebergs_",I8.8,"_restart.nc")') kt 
     172         WRITE(cl_filename,'(A,"_icebergs_",I8.8,"_restart.nc")') TRIM(cexper), kt 
    239173      ENDIF 
    240       IF (nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(cl_filename) 
    241  
    242       nret = NF90_CREATE(TRIM(cl_filename), NF90_CLOBBER, ncid) 
     174      IF (nn_verbose_level >= 0) WRITE(numout,'(2a)') 'icebergs, write_restart: creating ',TRIM(cl_path)//TRIM(cl_filename) 
     175 
     176      nret = NF90_CREATE(TRIM(cl_path)//TRIM(cl_filename), NF90_CLOBBER, ncid) 
    243177      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_create failed') 
    244178 
     
    256190      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim k failed') 
    257191 
     192      ! global attributes 
     193      IF( lk_mpp ) THEN 
     194         ! Set domain parameters (assume jpdom_local_full) 
     195         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ) 
     196         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number'         , narea-1            ) 
     197         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/1     , 2     /) ) 
     198         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/jpiglo, jpjglo/) ) 
     199         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/jpi   , jpj   /) ) 
     200         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/nimpp , njmpp /) ) 
     201         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/nimpp + jpi - 1 , njmpp + jpj - 1  /) ) 
     202         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/nldi - 1        , nldj - 1         /) ) 
     203         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/jpi - nlei      , jpj - nlej       /) ) 
     204         nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ) 
     205      ENDIF 
     206       
    258207      IF (associated(first_berg)) then 
    259208         nret = NF90_DEF_DIM(ncid, 'n', NF90_UNLIMITED, in_dim) 
     
    357306         ENDIF 
    358307      ENDDO 
    359       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: stored_ice  written' 
     308      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_ice  written' 
    360309 
    361310      nret = NF90_PUT_VAR( ncid, nkountid, num_bergs(:) ) 
     
    364313      nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
    365314      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
    366       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: stored_heat written' 
     315      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_heat written' 
    367316 
    368317      nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) ) 
     
    370319      nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
    371320      IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
    372       IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_filename),' var: calving written' 
     321      IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: calving written' 
    373322 
    374323      IF ( ASSOCIATED(first_berg) ) THEN 
Note: See TracChangeset for help on using the changeset viewer.