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

Changeset 14941


Ignore:
Timestamp:
2021-06-03T13:42:27+02:00 (3 years ago)
Author:
acc
Message:

#2605 : restartability and reproducibility fixes (at least for AMM12 with key_qco and key_RK3). Including: Sibylles corrected indexing of ssh in stprk3.F90; inclusion of before barotropic velocities in restarts (restart.F90 and istate.F90) and (as yet, unreviewed) changes to stprk3_stg.F90/trasbc.F90 to ensure correct stage calculations. A couple of other minor changes in module_example.F90 and mppini.F90 that the compiler flagged.

Location:
NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/DOM/istate.F90

    r14139 r14941  
    131131         ! 
    132132!!gm ==>>>  to be moved in usrdef_istate of C1D case  
    133          IF ( ln_uvd_init .AND. lk_c1d ) THEN ! read 3D U and V data at nit000 
    134             ALLOCATE( zuvd(jpi,jpj,jpk,2) ) 
    135             CALL dta_uvd( nit000, Kbb, zuvd ) 
    136             uu(:,:,:,Kbb) = zuvd(:,:,:,1)  ;  uu(:,:,:,Kmm) = uu(:,:,:,Kbb) 
    137             vv(:,:,:,Kbb) = zuvd(:,:,:,2)  ;  vv(:,:,:,Kmm) = vv(:,:,:,Kbb) 
    138             DEALLOCATE( zuvd ) 
    139          ENDIF 
    140          ! 
    141          !  
     133            IF ( ln_uvd_init .AND. lk_c1d ) THEN ! read 3D U and V data at nit000 
     134               ALLOCATE( zuvd(jpi,jpj,jpk,2) ) 
     135               CALL dta_uvd( nit000, Kbb, zuvd ) 
     136               uu(:,:,:,Kbb) = zuvd(:,:,:,1)  ;  uu(:,:,:,Kmm) = uu(:,:,:,Kbb) 
     137               vv(:,:,:,Kbb) = zuvd(:,:,:,2)  ;  vv(:,:,:,Kmm) = vv(:,:,:,Kbb) 
     138               DEALLOCATE( zuvd ) 
     139            ENDIF 
     140            ! 
    142141         ENDIF  
    143142#if defined key_agrif 
     
    145144#endif 
    146145      !  
    147       ! Initialize "now" and "before" barotropic velocities: 
    148       ! Do it whatever the free surface method, these arrays being eventually used 
     146      ! Initialize "now" barotropic velocities: 
     147      ! Do it whatever the free surface method, these arrays being used eventually  
    149148      ! 
    150149      uu_b(:,:,Kmm) = 0._wp   ;   vv_b(:,:,Kmm) = 0._wp 
    151       uu_b(:,:,Kbb) = 0._wp   ;   vv_b(:,:,Kbb) = 0._wp 
    152150      ! 
    153 !!gm  the use of umsak & vmask is not necessary below as uu(:,:,:,Kmm), vv(:,:,:,Kmm), uu(:,:,:,Kbb), vv(:,:,:,Kbb) are always masked 
     151!!gm  the use of umask & vmask is not necessary below as uu(:,:,:,Kmm), vv(:,:,:,Kmm), uu(:,:,:,Kbb), vv(:,:,:,Kbb) are always masked 
    154152      DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
    155153         uu_b(ji,jj,Kmm) = uu_b(ji,jj,Kmm) + e3u(ji,jj,jk,Kmm) * uu(ji,jj,jk,Kmm) * umask(ji,jj,jk) 
    156154         vv_b(ji,jj,Kmm) = vv_b(ji,jj,Kmm) + e3v(ji,jj,jk,Kmm) * vv(ji,jj,jk,Kmm) * vmask(ji,jj,jk) 
    157          ! 
    158          uu_b(ji,jj,Kbb) = uu_b(ji,jj,Kbb) + e3u(ji,jj,jk,Kbb) * uu(ji,jj,jk,Kbb) * umask(ji,jj,jk) 
    159          vv_b(ji,jj,Kbb) = vv_b(ji,jj,Kbb) + e3v(ji,jj,jk,Kbb) * vv(ji,jj,jk,Kbb) * vmask(ji,jj,jk) 
    160155      END_3D 
    161156      ! 
     
    163158      vv_b(:,:,Kmm) = vv_b(:,:,Kmm) * r1_hv(:,:,Kmm) 
    164159      ! 
    165       uu_b(:,:,Kbb) = uu_b(:,:,Kbb) * r1_hu(:,:,Kbb) 
    166       vv_b(:,:,Kbb) = vv_b(:,:,Kbb) * r1_hv(:,:,Kbb) 
     160      IF( .NOT. ln_rstart ) THEN 
     161         ! Initialize "before" barotropic velocities. "now" values are always set but  
     162         ! "before" values may have been read from a restart to ensure restartability. 
     163         ! In the non-restart case they need to be initialised here: 
     164         uu_b(:,:,Kbb) = 0._wp   ;   vv_b(:,:,Kbb) = 0._wp 
     165         DO_3D( 1, 1, 1, 1, 1, jpkm1 ) 
     166            uu_b(ji,jj,Kbb) = uu_b(ji,jj,Kbb) + e3u(ji,jj,jk,Kbb) * uu(ji,jj,jk,Kbb) * umask(ji,jj,jk) 
     167            vv_b(ji,jj,Kbb) = vv_b(ji,jj,Kbb) + e3v(ji,jj,jk,Kbb) * vv(ji,jj,jk,Kbb) * vmask(ji,jj,jk) 
     168         END_3D 
     169         uu_b(:,:,Kbb) = uu_b(:,:,Kbb) * r1_hu(:,:,Kbb) 
     170         vv_b(:,:,Kbb) = vv_b(:,:,Kbb) * r1_hv(:,:,Kbb) 
     171         !  
     172      ENDIF 
    167173      ! 
    168174   END SUBROUTINE istate_init 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/IOM/restart.F90

    r14800 r14941  
    165165         CALL iom_rstput( kt, nitrst, numrow, 'ub'     , uu(:,:,:       ,Kbb) ) 
    166166         CALL iom_rstput( kt, nitrst, numrow, 'vb'     , vv(:,:,:       ,Kbb) ) 
     167         CALL iom_rstput( kt, nitrst, numrow, 'uu_b'   , uu_b(:,:       ,Kbb) )     ! before fields 
     168         CALL iom_rstput( kt, nitrst, numrow, 'vv_b'   , vv_b(:,:       ,Kbb) )     ! before fields 
    167169         IF( .NOT.lk_SWE ) THEN 
    168170            CALL iom_rstput( kt, nitrst, numrow, 'tb'  , ts(:,:,:,jp_tem,Kbb) ) 
     
    288290      CALL iom_get( numror, jpdom_auto, 'ub'   , uu(:,:,:       ,Kbb), cd_type = 'U', psgn = -1._wp ) 
    289291      CALL iom_get( numror, jpdom_auto, 'vb'   , vv(:,:,:       ,Kbb), cd_type = 'V', psgn = -1._wp ) 
     292      CALL iom_get( numror, jpdom_auto, 'uu_b'   , uu_b(:,:     ,Kbb), cd_type = 'U', psgn = -1._wp ) 
     293      CALL iom_get( numror, jpdom_auto, 'vv_b'   , vv_b(:,:     ,Kbb), cd_type = 'V', psgn = -1._wp ) 
    290294      IF( .NOT.lk_SWE ) THEN 
    291295         CALL iom_get( numror, jpdom_auto, 'tb', ts(:,:,:,jp_tem,Kbb) ) 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/LBC/mppini.F90

    r14275 r14941  
    10711071         IF( iarea < MOD(Nj0glo,iproc) ) ijsz = ijsz + 1 
    10721072         ijstr = iarea*(Nj0glo/iproc) + MIN(iarea, MOD(Nj0glo,iproc)) + 1    ! starting j position of the reading 
     1073         IF( ijstr + ijsz > Nj0glo ) ijsz = Nj0glo - ijstr                   ! avoid reading past the end of the array 
    10731074         ! 
    10741075         ALLOCATE( lloce(Ni0glo, ijsz) )                                     ! allocate the strip 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/TRA/trasbc.F90

    r14784 r14941  
    122122      !---------------------------------------- 
    123123      !                             !==  Set before sbc tracer content fields  ==! 
     124      zfact = 0.5_wp 
    124125      IF( kt == nit000 .AND. istg_1 == 1 ) THEN             !* 1st time-step 
    125126         IF( ln_rstart .AND. .NOT.l_1st_euler ) THEN      ! Restart: read in restart file 
    126             zfact = 0.5_wp 
    127127            IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile 
    128128               IF(lwp) WRITE(numout,*) '          nit000-1 sbc tracer content field read in the restart file' 
     
    143143            sbc_tsc_b(ji,jj,:) = sbc_tsc(ji,jj,:) 
    144144         END_2D 
     145         IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
     146            IF( lrst_oce ) THEN           !==  write sbc_tsc in the ocean restart file  ==! 
     147               CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem) ) 
     148               CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal) ) 
     149            ENDIF 
     150         ENDIF 
    145151      ENDIF 
    146152      !                             !==  Now sbc tracer content fields  ==! 
     
    167173      END DO 
    168174      ! 
    169       IF( ntile == 0 .OR. ntile == nijtile )  THEN                ! Do only on the last tile 
    170          IF( lrst_oce ) THEN           !==  write sbc_tsc in the ocean restart file  ==! 
    171             CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem) ) 
    172             CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal) ) 
    173          ENDIF 
    174       ENDIF 
    175175      ! 
    176176      !---------------------------------------- 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/module_example.F90

    r14041 r14941  
    189189CONTAINS 
    190190   SUBROUTINE exa_mpl( kt, pvar1, pvar2, ptab )              ! Empty routine 
    191       REAL::   ptab(:,:) 
     191      REAL::   pvar1, pvar2, ptab(:,:) 
     192      INTEGER :: kt 
    192193      WRITE(*,*) 'exa_mpl: You should not have seen this print! error?', kt, pvar1, pvar2, ptab(1,1) 
    193194   END SUBROUTINE exa_mpl 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/stprk3.F90

    r14800 r14941  
    122122      IF( ln_tide    )   CALL tide_update( kstp )                          ! update tide potential 
    123123      IF( ln_apr_dyn )   CALL sbc_apr    ( kstp )                          ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib) 
    124       IF( ln_bdy     )   CALL bdy_dta    ( kstp, Nnn )                     ! update dynamic & tracer data at open boundaries 
    125       IF( ln_isf     )   CALL isf_stp    ( kstp, Nnn )                     ! update iceshelf geometry 
    126                          CALL sbc        ( kstp, Nbb, Nnn )                ! Sea Boundary Condition (including sea-ice) 
     124      IF( ln_bdy     )   CALL bdy_dta    ( kstp, Nbb )                     ! update dynamic & tracer data at open boundaries 
     125      IF( ln_isf     )   CALL isf_stp    ( kstp, Nbb )                     ! update iceshelf geometry 
     126                         CALL sbc        ( kstp, Nbb, Nbb )                ! Sea Boundary Condition (including sea-ice) 
    127127 
    128128      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    140140!!gm only Before is needed for bn2 and rab  (except at stage 3 for n2) 
    141141!!gm issue with   Nnn  used in rad(Nbb)  
    142                          CALL eos_rab( ts(:,:,:,:,Nbb), rab_b, Nnn )       ! before local thermal/haline expension ratio at T-points 
     142                         CALL eos_rab( ts(:,:,:,:,Nbb), rab_b, Nbb )       ! before local thermal/haline expension ratio at T-points 
    143143!!st                         CALL eos_rab( ts(:,:,:,:,Nnn), rab_n, Nnn )       ! now    local thermal/haline expension ratio at T-points 
    144                          CALL bn2    ( ts(:,:,:,:,Nbb), rab_b, rn2b, Nnn ) ! before Brunt-Vaisala frequency 
     144                         CALL bn2    ( ts(:,:,:,:,Nbb), rab_b, rn2b, Nbb ) ! before Brunt-Vaisala frequency 
    145145!!st                         CALL bn2    ( ts(:,:,:,:,Nnn), rab_n, rn2, Nnn  ) ! now    Brunt-Vaisala frequency 
    146146!!gm 
     
    160160 
    161161         IF( ln_zps .AND. .NOT. ln_isfcav)                                    & 
    162             &            CALL zps_hde    ( kstp, Nnn, jpts, ts(:,:,:,:,Nbb), gtsu, gtsv,  &  ! Partial steps: before horizontal gradient 
     162            &            CALL zps_hde    ( kstp, Nbb, jpts, ts(:,:,:,:,Nbb), gtsu, gtsv,  &  ! Partial steps: before horizontal gradient 
    163163            &                                          rhd, gru , grv    )       ! of t, s, rd at the last ocean level 
    164164 
    165165         IF( ln_zps .AND.       ln_isfcav)                                                & 
    166             &            CALL zps_hde_isf( kstp, Nnn, jpts, ts(:,:,:,:,Nbb), gtsu, gtsv, gtui, gtvi,  &  ! Partial steps for top cell (ISF) 
     166            &            CALL zps_hde_isf( kstp, Nbb, jpts, ts(:,:,:,:,Nbb), gtsu, gtsv, gtui, gtvi,  &  ! Partial steps for top cell (ISF) 
    167167            &                                          rhd, gru , grv , grui, grvi   )       ! of t, s, rd at the first ocean level 
    168168         IF( ln_traldf_triad ) THEN 
    169                          CALL ldf_slp_triad( kstp, Nbb, Nnn )             ! before slope for triad operator 
     169                         CALL ldf_slp_triad( kstp, Nbb, Nbb )             ! before slope for triad operator 
    170170         ELSE 
    171                          CALL ldf_slp     ( kstp, rhd, rn2b, Nbb, Nnn )   ! before slope for standard operator 
     171                         CALL ldf_slp     ( kstp, rhd, rn2b, Nbb, Nbb )   ! before slope for standard operator 
    172172         ENDIF 
    173173      ENDIF 
    174174      !                                                                        ! eddy diffusivity coeff. 
    175       IF( l_ldftra_time .OR. l_ldfeiv_time )   CALL ldf_tra( kstp, Nbb, Nnn )  !       and/or eiv coeff. 
     175      IF( l_ldftra_time .OR. l_ldfeiv_time )   CALL ldf_tra( kstp, Nbb, Nbb )  !       and/or eiv coeff. 
    176176      IF( l_ldfdyn_time                    )   CALL ldf_dyn( kstp, Nbb )       ! eddy viscosity coeff. 
    177177 
  • NEMO/branches/2021/dev_r14318_RK3_stage1/src/OCE/stprk3_stg.F90

    r14800 r14941  
    213213!===>>>>>> stg1&2:  Verify the necessity of these trends (we may need it as there are in the RHS of dynspg_ts ?) 
    214214!!gm ====>>>>   needed for heat and salt fluxes associated with mass/volume flux 
    215                         CALL tra_sbc( kstp,      Kmm, ts, Krhs )   ! surface boundary condition 
     215                        CALL tra_sbc( kstp,      Kmm, ts, Krhs, kstg )   ! surface boundary condition 
    216216 
    217217      IF( ln_isf )      CALL tra_isf( kstp,      Kmm, ts, Krhs )   ! ice shelf heat flux 
Note: See TracChangeset for help on using the changeset viewer.