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 12745 – NEMO

Changeset 12745


Ignore:
Timestamp:
2020-04-14T08:14:07+02:00 (4 years ago)
Author:
smasson
Message:

Extra_Halo: iom cleaning and fix ICB restartability, see #2366

Location:
NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ICB/icb_oce.F90

    r12472 r12745  
    147147   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldexpect                    !: nfold expected number of bergs 
    148148   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   nicbfldreq                       !: nfold message handle (immediate send) 
    149  
    150    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   :: griddata                           !: work array for icbrst 
    151  
    152149   !!---------------------------------------------------------------------- 
    153150   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    196193      icb_alloc = icb_alloc + ill 
    197194 
    198       ALLOCATE( griddata(jpi,jpj,1), STAT=ill ) 
    199       icb_alloc = icb_alloc + ill 
    200  
    201195      CALL mpp_sum ( 'icb_oce', icb_alloc ) 
    202196      IF( icb_alloc > 0 )   CALL ctl_warn('icb_alloc: allocation of arrays failed') 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ICB/icbrst.F90

    r12738 r12745  
    9191            ij = INT( localpt%yj + 0.5 ) 
    9292            ! 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/) ) 
     93            IF ( ii >= mig(nldi) .AND. ii <= mig(nlei) .AND.  & 
     94           &     ij >= mjg(nldj) .AND. ij <= mjg(nlej) ) THEN            
     95 
     96               CALL iom_get( ncid, jpdom_unknown, 'number', zdata(:) , ktime=jn, kstart=(/1/), kcount=(/nkounts/) ) 
    9797               localberg%number(:) = INT(zdata(:)) 
    9898               imax_icb = MAX( imax_icb, INT(zdata(1)) ) 
     
    126126      CALL iom_get( ncid, jpdom_auto,    'calving_hflx', src_calving_hflx  ) 
    127127      CALL iom_get( ncid, jpdom_auto,    'stored_heat' , berg_grid%stored_heat  ) 
    128       CALL iom_get( ncid, jpdom_auto_xy, 'stored_ice'  , berg_grid%stored_ice, kstart=(/1,1,1/), kcount=(/1,1,nclasses/) ) 
     128      ! with jpdom_auto_xy, ue use only the third element of kstart and kcount. 
     129      CALL iom_get( ncid, jpdom_auto_xy, 'stored_ice'  , berg_grid%stored_ice, kstart=(/-99,-99,1/), kcount=(/-99,-99,nclasses/) ) 
    129130       
    130131      CALL iom_get( ncid, jpdom_unknown, 'kount' , zdata(:) ) 
     
    225226    
    226227         ! Dimensions 
    227          nret = NF90_DEF_DIM(ncid, 'x', jpi, ix_dim) 
     228         nret = NF90_DEF_DIM(ncid, 'x', nlei-nldi+1, ix_dim) 
    228229         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim x failed') 
    229230    
    230          nret = NF90_DEF_DIM(ncid, 'y', jpj, iy_dim) 
     231         nret = NF90_DEF_DIM(ncid, 'y', nlej-nldj+1, iy_dim) 
    231232         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_def_dim y failed') 
    232233    
     
    242243            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ) 
    243244            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_number'         , narea-1            ) 
    244             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/1     , 2     /) ) 
    245             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/jpiglo, jpjglo/) ) 
    246             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/jpi   , jpj  /) ) 
    247             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/nimpp , njmpp /) ) 
    248             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/nimpp + jpi - 1 , njmpp + jpj - 1  /) ) 
    249             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/nldi - 1        , nldj - 1         /) ) 
    250             nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/jpi - nlei      , jpj - nlej       /) ) 
     245            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_dimensions_ids' , (/ 1              , 2               /) ) 
     246            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_global'    , (/ jpiglo         , jpjglo          /) ) 
     247            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_size_local'     , (/ nlei - nldi + 1, nlej - nldj + 1 /) ) 
     248            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_first' , (/ mig(nldi)      , mjg(nldj)      /) ) 
     249            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_position_last'  , (/ mig(nlei)      , mjg(nlej)       /) ) 
     250            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_start', (/ 0              , 0               /) ) 
     251            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_halo_size_end'  , (/ 0              , 0               /) ) 
    251252            nret = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'DOMAIN_type'           , 'BOX'              ) 
    252253         ENDIF 
     
    340341         nstrt3(1) = 1 
    341342         nstrt3(2) = 1 
    342          nlngth3(1) = jpi 
    343          nlngth3(2) = jpj 
     343         nlngth3(1) = nlei - nldi + 1 
     344         nlngth3(2) = nlej - nldj + 1 
    344345         nlngth3(3) = 1 
    345346    
    346347         DO jn=1,nclasses 
    347             griddata(:,:,1) = berg_grid%stored_ice(:,:,jn) 
    348348            nstrt3(3) = jn 
    349             nret = NF90_PUT_VAR( ncid, nsiceid, griddata, nstrt3, nlngth3 ) 
     349            nret = NF90_PUT_VAR( ncid, nsiceid, berg_grid%stored_ice(nldi:nlei,nldj:nlej,jn), nstrt3, nlngth3 ) 
    350350            IF (nret .ne. NF90_NOERR) THEN 
    351351               IF( lwp ) WRITE(numout,*) TRIM(NF90_STRERROR( nret )) 
     
    358358         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var kount failed') 
    359359    
    360          nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(:,:) ) 
     360         nret = NF90_PUT_VAR( ncid, nsheatid, berg_grid%stored_heat(nldi:nlei,nldj:nlej) ) 
    361361         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var stored_heat failed') 
    362362         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: stored_heat written' 
    363363    
    364          nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(:,:) ) 
     364         nret = NF90_PUT_VAR( ncid, ncalvid , src_calving(nldi:nlei,nldj:nlej) ) 
    365365         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving failed') 
    366          nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(:,:) ) 
     366         nret = NF90_PUT_VAR( ncid, ncalvhid, src_calving_hflx(nldi:nlei,nldj:nlej) ) 
    367367         IF (nret .ne. NF90_NOERR) CALL ctl_stop('icebergs, write_restart: nf_put_var calving_hflx failed') 
    368368         IF( lwp ) WRITE(numout,*) 'file: ',TRIM(cl_path)//TRIM(cl_filename),' var: calving written' 
  • NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/IOM/iom.F90

    r12738 r12745  
    762762      ENDIF 
    763763      IF( llwrt ) THEN 
    764          idompar(:,1) = (/ nlei  - nldi + 1, nlej - nldj + 1 /) 
    765          idompar(:,2) = (/ nimpp + nldi - 1, njmpp + nldj - 1 /) 
    766          idompar(:,3) = (/ nimpp + nlei - 1, njmpp + nlej - 1 /) 
    767          idompar(:,4) = (/ 0               , 0                /) 
    768          idompar(:,5) = (/ 0               , 0                /) 
     764         idompar(:,1) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
     765         idompar(:,2) = (/ mig(nldi)      , mjg(nldj)      /) 
     766         idompar(:,3) = (/ mig(nlei)      , mjg(nlej)      /) 
     767         idompar(:,4) = (/ 0              , 0               /) 
     768         idompar(:,5) = (/ 0              , 0               /) 
    769769      ENDIF 
    770770      ! Open the NetCDF file 
     
    10811081         IF( PRESENT(kcount) .AND. .NOT. PRESENT(kstart) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 
    10821082         IF( PRESENT(kstart) .AND. .NOT. PRESENT(kcount) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 
    1083          IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND.  idom /= jpdom_auto_xy ) & 
     1083         IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND. idom /= jpdom_auto_xy ) & 
    10841084            &          CALL ctl_stop(TRIM(clinfo), 'kstart present needs idom = jpdom_unknown or idom = jpdom_auto_xy') 
     1085         IF( idom == jpdom_auto_xy .AND. .NOT. PRESENT(kstart) ) & 
     1086            &          CALL ctl_stop(TRIM(clinfo), 'idom = jpdom_auto_xy requires kstart to be present') 
    10851087         ! 
    10861088         ! Search for the variable in the data base (eventually actualize data) 
     
    10961098            ! 
    10971099            ! Identify the domain in case of jpdom_auto definition 
    1098             ll_only3rd = idom == jpdom_auto_xy             ! depth is specified if idom == jpdom_auto_xy  
    10991100            IF( idom == jpdom_auto .OR. idom == jpdom_auto_xy ) THEN             
    11001101               idom = jpdom_global   ! default 
     
    11451146            ! definition of istart and icnt 
    11461147            ! 
    1147             icnt  (:) = 1   ! default definition (simple way to deal with special cases listed above)  
    1148             istart(:) = 1   ! default definition (simple way to deal with special cases listed above)  
    1149             istart(idmspc+1) = itime 
     1148            icnt  (:) = 1              ! default definition (simple way to deal with special cases listed above)  
     1149            istart(:) = 1              ! default definition (simple way to deal with special cases listed above)  
     1150            istart(idmspc+1) = itime   ! temporal dimenstion 
    11501151            ! 
    1151             IF( PRESENT(kstart) .AND. .NOT. ll_only3rd ) THEN  
    1152                istart(1:idmspc) = kstart(1:idmspc)  
    1153                icnt  (1:idmspc) = kcount(1:idmspc) 
    1154             ELSE 
    1155                IF(idom == jpdom_unknown ) THEN 
    1156                   icnt(1:idmspc) = idimsz(1:idmspc) 
    1157                ELSE  
    1158                   IF( .NOT. PRESENT(pv_r1d) ) THEN   !   not a 1D array 
    1159                      ! we do not read the overlap and the extra-halos -> from nldi to nlei and from nldj to nlej  
    1160                      IF( idom == jpdom_global )   istart(1:2) = (/ mig(nldi), mjg(nldj) /) 
    1161                      icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
    1162                      IF( PRESENT(pv_r3d) ) THEN 
    1163                         IF( ll_only3rd .AND. PRESENT(kstart) ) THEN   ;   istart(3) = kstart(3)   ;   icnt(3) = kcount(3) 
    1164                         ELSE                                          ;                               icnt(3) = inlev 
    1165                         ENDIF 
    1166                      ENDIF 
     1152            IF( idom == jpdom_unknown ) THEN 
     1153               IF( PRESENT(kstart) .AND. idom /= jpdom_auto_xy ) THEN  
     1154                  istart(1:idmspc) = kstart(1:idmspc)  
     1155                  icnt  (1:idmspc) = kcount(1:idmspc) 
     1156               ELSE 
     1157                  icnt  (1:idmspc) = idimsz(1:idmspc) 
     1158               ENDIF 
     1159            ELSE   !   not a 1D array as pv_r1d requires jpdom_unknown 
     1160               ! we do not read the overlap and the extra-halos -> from nldi to nlei and from nldj to nlej  
     1161               IF( idom == jpdom_global )   istart(1:2) = (/ mig(nldi), mjg(nldj) /) 
     1162               icnt(1:2) = (/ nlei - nldi + 1, nlej - nldj + 1 /) 
     1163               IF( PRESENT(pv_r3d) ) THEN 
     1164                  IF( idom == jpdom_auto_xy ) THEN 
     1165                     istart(3) = kstart(3) 
     1166                     icnt  (3) = kcount(3) 
     1167                  ELSE 
     1168                     icnt  (3) = inlev 
    11671169                  ENDIF 
    11681170               ENDIF 
Note: See TracChangeset for help on using the changeset viewer.