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 5865 for branches – NEMO

Changeset 5865 for branches


Ignore:
Timestamp:
2015-11-05T17:53:38+01:00 (8 years ago)
Author:
davestorkey
Message:

IOM-inification of reading of iceberg restarts.

Location:
branches/UKMO/icebergs_restart_single_file/NEMOGCM/NEMO/OPA_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/icebergs_restart_single_file/NEMOGCM/NEMO/OPA_SRC/ICB/icbrst.F90

    r5852 r5865  
    2222   USE lib_mpp        ! NEMO MPI library, lk_mpp in particular 
    2323   USE netcdf         ! netcdf routines for IO 
     24   USE iom 
    2425   USE icb_oce        ! define iceberg arrays 
    2526   USE icbutl         ! iceberg utility routines 
     
    6970      TYPE(iceberg)                ::   localberg ! NOT a pointer but an actual local variable 
    7071      TYPE(point)                  ::   localpt   ! NOT a pointer but an actual local variable 
    71       !!---------------------------------------------------------------------- 
    72  
    73       ! Find a restart file. Assume iceberg restarts in same directory as ocean restarts.  
     72      REAL(wp), DIMENSION(1,nkounts) ::   rdata_in  
     73      !!---------------------------------------------------------------------- 
     74 
     75      ! Find a restart file. Assume iceberg restarts in same directory as ocean restarts 
     76      ! and are called TRIM(cn_ocerst)//'_icebergs' 
    7477      cl_path = TRIM(cn_ocerst_indir) 
    7578      IF( cl_path(LEN_TRIM(cl_path):) /= '/' ) cl_path = TRIM(cl_path) // '/' 
    76       cl_filename = ' ' 
    77       IF ( lk_mpp ) THEN 
    78          cl_filename = ' ' 
    79          WRITE( cl_filename, '("restart_icebergs_",I4.4,".nc")' ) narea-1 
    80          INQUIRE( file=TRIM(cl_path)//TRIM(cl_filename), exist=ll_found_restart ) 
    81       ELSE 
    82          cl_filename = 'restart_icebergs.nc' 
    83          INQUIRE( file=TRIM(cl_path)//TRIM(cl_filename), exist=ll_found_restart ) 
    84       ENDIF 
    85  
    86       IF ( .NOT. ll_found_restart) THEN                     ! only do the following if a file was found 
    87          CALL ctl_stop('icebergs: no restart file found') 
    88       ENDIF 
    89  
    90       IF (nn_verbose_level >= 0 .AND. lwp)  & 
    91          WRITE(numout,'(2a)') 'icebergs, read_restart_bergs: found restart file = ',TRIM(cl_path)//TRIM(cl_filename) 
    92  
    93       nret = NF90_OPEN(TRIM(cl_path)//TRIM(cl_filename), NF90_NOWRITE, ncid) 
    94       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_open failed') 
    95  
    96       nret = nf90_inquire(ncid, idim, ivar, iatt, iunlim_dim) 
    97       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inquire failed') 
    98  
    99       IF( iunlim_dim .NE. -1) THEN 
    100  
    101          nret = nf90_inquire_dimension(ncid, iunlim_dim, cl_dname, ibergs_in_file) 
    102          IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart_bergs: nf_inq_dimlen failed') 
    103  
    104          nret = NF90_INQ_VARID(ncid, 'number', numberid) 
    105          nret = NF90_INQ_VARID(ncid, 'mass_scaling', nscaling_id) 
    106          nret = NF90_INQ_VARID(ncid, 'xi', nxid) 
    107          nret = NF90_INQ_VARID(ncid, 'yj', nyid) 
    108          nret = NF90_INQ_VARID(ncid, 'lon', nlonid) 
    109          nret = NF90_INQ_VARID(ncid, 'lat', nlatid) 
    110          nret = NF90_INQ_VARID(ncid, 'uvel', nuvelid) 
    111          nret = NF90_INQ_VARID(ncid, 'vvel', nvvelid) 
    112          nret = NF90_INQ_VARID(ncid, 'mass', nmassid) 
    113          nret = NF90_INQ_VARID(ncid, 'thickness', nthicknessid) 
    114          nret = NF90_INQ_VARID(ncid, 'width', nwidthid) 
    115          nret = NF90_INQ_VARID(ncid, 'length', nlengthid) 
    116          nret = NF90_INQ_VARID(ncid, 'year', nyearid) 
    117          nret = NF90_INQ_VARID(ncid, 'day', ndayid) 
    118          nret = NF90_INQ_VARID(ncid, 'mass_of_bits', nmass_of_bits_id) 
    119          nret = NF90_INQ_VARID(ncid, 'heat_density', nheat_density_id) 
    120  
    121          ilngth(1) = 1 
    122          istrt2(1) = 1 
    123          ilngth2(1) = nkounts 
    124          ilngth2(2) = 1 
    125          DO jn=1, ibergs_in_file 
    126  
    127             istrt(1) = jn 
    128             istrt2(2) = jn 
    129  
    130             nret = NF90_GET_VAR(ncid, numberid, idata2, istrt2, ilngth2 ) 
    131             localberg%number(:) = idata2(:) 
    132  
    133             nret = NF90_GET_VAR(ncid, nscaling_id, zdata, istrt, ilngth ) 
    134             localberg%mass_scaling = zdata(1) 
    135  
    136             nret = NF90_GET_VAR(ncid, nlonid, zdata, istrt, ilngth) 
    137             localpt%lon = zdata(1) 
    138             nret = NF90_GET_VAR(ncid, nlatid, zdata, istrt, ilngth) 
    139             localpt%lat = zdata(1) 
    140             IF (nn_verbose_level >= 2 .AND. lwp) THEN 
    141                WRITE(numout,'(a,i5,a,2f10.4,a,i5)') 'icebergs, read_restart_bergs: berg ',jn,' is at ', & 
    142                                               localpt%lon,localpt%lat,' on PE ',narea-1 
     79      cl_filename = TRIM(cn_ocerst_in)//'_icebergs' 
     80      CALL iom_open( TRIM(cl_path)//cl_filename, ncid ) 
     81 
     82      IF( iom_file(ncid)%iduld .GE. 0) THEN 
     83 
     84         ibergs_in_file = iom_file(ncid)%lenuld 
     85         IF(lwp) WRITE(numout,*) '>>> Number of bergs in local file : ',ibergs_in_file 
     86         DO jn = 1,ibergs_in_file 
     87 
     88            ! iom_get treats the unlimited dimension as time. Here the unlimited dimension  
     89            ! is the iceberg index, but we can still use the ktime keyword to get the iceberg we want.  
     90 
     91            CALL iom_get( ncid, 'xi'     ,localpt%xi  , ktime=jn ) 
     92            CALL iom_get( ncid, 'yj'     ,localpt%yj  , ktime=jn ) 
     93 
     94            IF(lwp) WRITE(numout, *) '>>> Found iceberg ',jn,' at (i,j) ',localpt%xi,',',localpt%yj 
     95            IF(lwp) WRITE(numout, *) '>>> nldi, nlei, nldj, nlej, nimpp, njmpp ',nldi, nlei, nldj, nlej, nimpp, njmpp 
     96 
     97            ! Only proceed if this iceberg is on the local processor (including halos). 
     98            IF ( localpt%xi .GE. nimpp .AND. localpt%xi .LE. nimpp+jpi-1 .AND. & 
     99           &     localpt%yj .GE. njmpp .AND. localpt%yj .LE. njmpp+jpj-1 ) THEN            
     100 
     101               CALL iom_get( ncid, jpdom_unknown, 'number'       , (/rdata_in(1,:)/) , ktime=jn, kstart=(/1/), kcount=(/nkounts/) ) 
     102               localberg%number(:) = INT(rdata_in(1,:)) 
     103               CALL iom_get( ncid, 'mass_scaling' , localberg%mass_scaling, ktime=jn ) 
     104               CALL iom_get( ncid, 'lon'          , localpt%lon           , ktime=jn ) 
     105               CALL iom_get( ncid, 'lat'          , localpt%lat           , ktime=jn ) 
     106               CALL iom_get( ncid, 'uvel'         , localpt%uvel          , ktime=jn ) 
     107               CALL iom_get( ncid, 'vvel'         , localpt%vvel          , ktime=jn ) 
     108               CALL iom_get( ncid, 'mass'         , localpt%mass          , ktime=jn ) 
     109               CALL iom_get( ncid, 'thickness'    , localpt%thickness     , ktime=jn ) 
     110               CALL iom_get( ncid, 'width'        , localpt%width         , ktime=jn ) 
     111               CALL iom_get( ncid, 'length'       , localpt%length        , ktime=jn ) 
     112               CALL iom_get( ncid, 'year'         , rdata_in(1,1)         , ktime=jn ) 
     113               localpt%year = INT(rdata_in(1,1)) 
     114               CALL iom_get( ncid, 'day'          , localpt%day           , ktime=jn ) 
     115               CALL iom_get( ncid, 'mass_of_bits' , localpt%mass_of_bits  , ktime=jn ) 
     116               CALL iom_get( ncid, 'heat_density' , localpt%heat_density  , ktime=jn ) 
     117 
     118               ! 
     119               IF(lwp) WRITE(numout, *) '>>> Initialising iceberg ',jn,' at (i,j) ',localpt%xi,',',localpt%yj 
     120               CALL icb_utl_add( localberg, localpt ) 
     121 
    143122            ENDIF 
    144             nret = NF90_GET_VAR(ncid, nxid, zdata, istrt, ilngth) 
    145             localpt%xi = zdata(1) 
    146             nret = NF90_GET_VAR(ncid, nyid, zdata, istrt, ilngth) 
    147             localpt%yj = zdata(1) 
    148             nret = NF90_GET_VAR(ncid, nuvelid, zdata, istrt, ilngth ) 
    149             localpt%uvel = zdata(1) 
    150             nret = NF90_GET_VAR(ncid, nvvelid, zdata, istrt, ilngth ) 
    151             localpt%vvel = zdata(1) 
    152             nret = NF90_GET_VAR(ncid, nmassid, zdata, istrt, ilngth ) 
    153             localpt%mass = zdata(1) 
    154             nret = NF90_GET_VAR(ncid, nthicknessid, zdata, istrt, ilngth ) 
    155             localpt%thickness = zdata(1) 
    156             nret = NF90_GET_VAR(ncid, nwidthid, zdata, istrt, ilngth ) 
    157             localpt%width = zdata(1) 
    158             nret = NF90_GET_VAR(ncid, nlengthid, zdata, istrt, ilngth ) 
    159             localpt%length = zdata(1) 
    160             nret = NF90_GET_VAR(ncid, nyearid, idata, istrt, ilngth ) 
    161             localpt%year = idata(1) 
    162             nret = NF90_GET_VAR(ncid, ndayid, zdata, istrt, ilngth ) 
    163             localpt%day = zdata(1) 
    164             nret = NF90_GET_VAR(ncid, nmass_of_bits_id, zdata, istrt, ilngth ) 
    165             localpt%mass_of_bits = zdata(1) 
    166             nret = NF90_GET_VAR(ncid, nheat_density_id, zdata, istrt, ilngth ) 
    167             localpt%heat_density = zdata(1) 
    168             ! 
    169             CALL icb_utl_add( localberg, localpt ) 
     123 
    170124         END DO 
    171          ! 
    172       ENDIF 
    173  
    174       nret = NF90_INQ_DIMID( ncid, 'c', nc_dim ) 
    175       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inq_dimid c failed') 
    176  
    177       nret = NF90_INQUIRE_DIMENSION( ncid, nc_dim, cl_dname, iclass ) 
    178       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_inquire_dimension failed') 
    179  
    180       nret = NF90_INQ_VARID(ncid, 'kount'       , nkountid) 
    181       nret = NF90_INQ_VARID(ncid, 'calving'     , ncalvid) 
    182       nret = NF90_INQ_VARID(ncid, 'calving_hflx', ncalvhid) 
    183       nret = NF90_INQ_VARID(ncid, 'stored_ice'  , nsiceid) 
    184       nret = NF90_INQ_VARID(ncid, 'stored_heat' , nsheatid) 
    185  
    186       nstrt3(1) = 1 
    187       nstrt3(2) = 1 
    188       nlngth3(1) = jpi 
    189       nlngth3(2) = jpj 
    190       nlngth3(3) = 1 
    191  
    192       DO jn = 1, iclass 
    193          nstrt3(3) = jn 
    194          nret      = NF90_GET_VAR( ncid, nsiceid , griddata, nstrt3, nlngth3 ) 
    195          berg_grid%stored_ice(:,:,jn) = griddata(:,:,1) 
    196       END DO 
    197  
    198       nret = NF90_GET_VAR( ncid, ncalvid , src_calving          (:,:) ) 
    199       nret = NF90_GET_VAR( ncid, ncalvhid, src_calving_hflx     (:,:) ) 
    200       nret = NF90_GET_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
    201       nret = NF90_GET_VAR( ncid, nkountid, idata2(:) ) 
    202       num_bergs(:) = idata2(:) 
     125 
     126      ENDIF  
     127 
     128      ! Gridded variables 
     129      CALL iom_get( ncid, jpdom_autoglo,    'calving'     , src_calving  ) 
     130      CALL iom_get( ncid, jpdom_autoglo,    'calving_hflx', src_calving_hflx  ) 
     131      CALL iom_get( ncid, jpdom_autoglo,    'stored_heat' , berg_grid%stored_heat  ) 
     132      CALL iom_get( ncid, jpdom_autoglo_xy, 'stored_ice'  , berg_grid%stored_ice, kstart=(/1,1,1/), kcount=(/1,1,nclasses/) ) 
     133       
     134      CALL iom_get( ncid, jpdom_unknown, 'kount' , (/rdata_in(1,:)/) ) 
     135      num_bergs(:) = INT(rdata_in(1,:)) 
    203136 
    204137      ! Finish up 
    205       nret = NF90_CLOSE(ncid) 
    206       IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, read_restart: nf_close failed') 
     138      CALL iom_close( ncid ) 
    207139 
    208140      ! Sanity check 
  • branches/UKMO/icebergs_restart_single_file/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r5852 r5865  
    685685      IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 
    686686      IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 
    687       IF( PRESENT(kstart) .AND. idom /= jpdom_unknown   ) CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown') 
     687      IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND.  idom /= jpdom_autoglo_xy  ) & 
     688     &           CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown or kdom = jpdom_autoglo_xy') 
    688689 
    689690      luse_jattr = .false. 
     
    771772         istart(idmspc+1) = itime 
    772773 
    773          IF(              PRESENT(kstart)      ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
     774         IF( PRESENT(kstart) .AND. idom /= jpdom_autoglo_xy ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 
    774775         ELSE 
    775             IF(           idom == jpdom_unknown ) THEN                                       ; icnt(1:idmspc) = idimsz(1:idmspc) 
     776            IF(           idom == jpdom_unknown ) THEN                                                ; icnt(1:idmspc) = idimsz(1:idmspc) 
    776777            ELSE  
    777778               IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array 
     
    796797                  ENDIF 
    797798                  IF( PRESENT(pv_r3d) ) THEN 
    798                      IF( idom == jpdom_data ) THEN   ; icnt(3) = jpkdta 
    799                      ELSE                            ; icnt(3) = jpk 
     799                     IF( idom == jpdom_data ) THEN                                  ; icnt(3) = jpkdta 
     800                     ELSE IF( idom == jpdom_autoglo_xy .AND. PRESENT(kstart) ) THEN ; istart(3) = kstart(3); icnt(3) = kcount(3) 
     801                     ELSE                                                           ; icnt(3) = jpk 
    800802                     ENDIF 
    801803                  ENDIF 
  • branches/UKMO/icebergs_restart_single_file/NEMOGCM/NEMO/OPA_SRC/IOM/iom_def.F90

    r5852 r5865  
    2626   INTEGER, PARAMETER, PUBLIC ::   jpdom_unknown       = 7   !: No dimension checking 
    2727   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo       = 8   !:  
    28    INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 9   !:  
     28   INTEGER, PARAMETER, PUBLIC ::   jpdom_autoglo_xy    = 9   !: Automatically set horizontal dimensions only 
     29   INTEGER, PARAMETER, PUBLIC ::   jpdom_autodta       = 10  !:  
    2930 
    3031   INTEGER, PARAMETER, PUBLIC ::   jpioipsl    = 100      !: Use ioipsl (fliocom only) library 
     
    5758      INTEGER                                   ::   nvars    !: number of identified varibles in the file 
    5859      INTEGER                                   ::   iduld    !: id of the unlimited dimension 
     60      INTEGER                                   ::   lenuld   !: length of the unlimited dimension (number of records in file) 
    5961      INTEGER                                   ::   irec     !: writing record position   
    6062      CHARACTER(LEN=32)                         ::   uldname  !: name of the unlimited dimension 
  • branches/UKMO/icebergs_restart_single_file/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r5852 r5865  
    154154         CALL iom_nf90_check(NF90_Inquire(if90id, unlimitedDimId = iom_file(kiomid)%iduld), clinfo) 
    155155         IF ( iom_file(kiomid)%iduld .GE. 0 ) THEN 
    156            CALL iom_nf90_check(NF90_Inquire_Dimension(if90id, iom_file(kiomid)%iduld,   & 
    157         &                                               name = iom_file(kiomid)%uldname), clinfo) 
     156           CALL iom_nf90_check(NF90_Inquire_Dimension(if90id, iom_file(kiomid)%iduld,     &  
     157        &                                               name = iom_file(kiomid)%uldname,  & 
     158        &                                               len  = iom_file(kiomid)%lenuld ), clinfo ) 
    158159         ENDIF 
    159160         IF(lwp) WRITE(numout,*) '                   ---> '//TRIM(cdname)//' OK' 
Note: See TracChangeset for help on using the changeset viewer.