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.
2021WP/KNL-01_Sibylle_RK3_stage1 – NEMO
wiki:2021WP/KNL-01_Sibylle_RK3_stage1

Version 21 (modified by techene, 2 years ago) (diff)

--

Name and subject of the action

Last edition: Wikinfo(changed_ts)? by Wikinfo(changed_by)?

The PI is responsible to closely follow the progress of the action, and especially to contact NEMO project manager if the delay on preview (or review) are longer than the 2 weeks expected.

  1. Summary
  2. Preview
  3. Tests
  4. Review

Summary

Action RK3 stage 1
PI(S) Gurvan et Sibylle
Digest Run a GYRE configuration with new RK3 scheme
Dependencies If any
Branch source:/NEMO/branches/2021/dev_r14318_RK3_stage1
Previewer(s) Gurvan
Reviewer(s) Names
Ticket #2605 #2715

Description

Error: Failed to load processor box
No macro or processor named 'box' found

RK3 time stepping implementation for NEMO includes at this stage dynamic and active tracers implementation, time spitting single first with 2D mode integration.

...

Implementation

Error: Failed to load processor box
No macro or processor named 'box' found

RK3 implementation is splitted up into :

  • code preparation
  • dynamic and active tracers (barocline)
  • vertical physics (TKE) ?
  • barotropic mode (barotrope)
  • mass forcing
  • passive tracers

Code preparation In order to preserve constancy property velocity for momentum and active tracers must be the same. Advection routines in flux form are modified to take (u,v,w) as an input argument. In order to use advection routines for the barotropic mode we need the possibility to de-activate vertical advection computation. Advection routines in flux and vector form are modified to take an optional argument (no_zad) to do so.

Barocline part For sake of simplicity we started to implement RK3 regarding a GYRE configuration validation with no barotrope mode (ssh, uu_b, un_adv are set to zero at each time step). Forcing have been removed except winds and heat flux. key_qco is active and vertical physics is modeled as constant with high viscosity coefficients.

  • Prepare routines
    • Change eos divhor and sshwzv interface.
  • Add RK3 time stepping routines
    • rk3stg deals with time integration at N+1/3, N+1/2 and N+1
    • stprk3 orchestrates

Barotrope part In order to validate 2D mode implementation we remove above zero forcing for barotropic variables mass forcing remains to zero.

  • Prepare routines
    • Change dynadv, dynvor, dynspg_ts
  • Add RK3 2D mode time stepping routines
    • rk3ssh prepare 2D forcing, get dynamics 2D RHS from 3D trends, integrate 2D mode

...

Implementation details : Code preparation

r14418 Allow an advective velocity to be passed as an argument.
3D velocity can be a pointer.

OCE
 |-- oce.F90
     REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:), TARGET   ::   uu   ,  vv     !: horizontal velocities        [m/s] 
     REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  , TARGET   ::   ww             !: vertical velocity            [m/s]

3D velocity added as an input argument of advective routines passed through dyn_adv

OCE
 |--DYN
     |-- dynadv.F90
         SUBROUTINE dyn_adv( kt, Kbb, Kmm, puu, pvv, Krhs, pau, pav, paw )
         ...
         CALL dyn_adv_cen2( kt                , Kmm, puu, pvv, Krhs, pau, pav, paw )   ! 2nd order centered scheme 
         CALL dyn_adv_ubs ( kt           , Kbb, Kmm, puu, pvv, Krhs, pau, pav, paw )   ! 3rd order UBS      scheme (UP3) 
     |-- dynadv_cen2.F90
         SUBROUTINE dyn_adv_cen2( kt, Kmm, puu, pvv, Krhs, pau, pav, paw )  
         ...       
         IF( PRESENT( pau ) ) THEN     ! RK3: advective velocity (pau,pav,paw) /= advected velocity (puu,pvv,ww) 
            zptu => pau(:,:,:) 
            ...
         zfu(:,:,jk) = 0.25_wp * e2u(:,:) * e3u(:,:,jk,Kmm) * zptu(:,:,jk) 
     |-- dynadv_ubs.F90
         SUBROUTINE dyn_adv_ubs( kt, Kbb, Kmm, puu, pvv, Krhs, pau, pav, paw ) 
         ...
         IF( PRESENT( pau ) ) THEN     ! RK3: advective velocity (pau,pav,paw) /= advected velocity (puu,pvv,ww) 
            zptu => pau(:,:,:) 
            ...
         zfu(:,:,jk) = e2u(:,:) * e3u(:,:,jk,Kmm) * zptu(:,:,jk) 
 |--TRA  
     |-- traadv.F90
         SUBROUTINE tra_adv( kt, Kbb, Kmm, pts, Krhs, pau, pav, paw ) 
         ...
         IF( PRESENT( pau ) ) THEN     ! RK3: advective velocity (pau,pav,paw) /= advected velocity (puu,pvv,ww) 
            zptu => pau(:,:,:) 
            ...
         zuu(ji,jj,jk) = e2u  (ji,jj) * e3u(ji,jj,jk,Kmm) * ( zptu(ji,jj,jk) + usd(ji,jj,jk) ) 

Finally this new structure is used in step and tested with usual velocities

OCE
 |-- stpmlf.F90
     REAL(wp), TARGET     , DIMENSION(jpi,jpj,jpk) ::   zau, zav, zaw   ! advective velocity 
     ...
     zau(:,:,:) = uu(:,:,:,Nnn)        !!st   patch for MLF will be computed in RK3
     ...
     CALL dyn_adv( kstp, Nbb, Nnn      , uu, vv, Nrhs, zau, zav, zaw )  ! advection (VF or FF)   ==> RHS
     ...
     CALL tra_adv    ( kstp, Nbb, Nnn, ts, Nrhs, zau, zav, zaw )  ! hor. + vert. advection ==> RHS 

Results should be exactly the same as the ones from from the trunk. It was not the case for an OVERFLOW. The use of ln_wAimp=T changes ww at the truncature in diawri.F90, and that produces a small error. This has been corrected.

r14428 Allow vertical advection to be de-activated with an optionnal input argument : no_zad.

3D velocity added as an input argument of advective routines passed through dyn_adv

OCE
 |--DYN
     |-- dynadv.F90
         SUBROUTINE dyn_adv( kt, Kbb, Kmm, puu, pvv, Krhs, pau, pav, paw, no_zad )
         ...
         CALL dyn_adv_cen2( kt                , Kmm, puu, pvv, Krhs, pau, pav, paw, no_zad )   ! 2nd order centered scheme 
         CALL dyn_adv_ubs ( kt           , Kbb, Kmm, puu, pvv, Krhs, pau, pav, paw, no_zad )   ! 3rd order UBS      scheme (UP3) 
     |-- dynadv_cen2.F90
         SUBROUTINE dyn_adv_cen2( kt, Kmm, puu, pvv, Krhs, pau, pav, paw, no_zad )  
         ...       
         IF( PRESENT( no_zad ) ) THEN  !==  No vertical advection  ==!   (except if linear free surface) 
            IF( ln_linssh ) THEN                ! linear free surface: advection through the surface z=0 
               DO_2D( 0, 0, 0, 0 ) 
                  zzu = 0.5_wp * ( e1e2t(ji,jj) * zpt_w(ji,jj,1) + e1e2t(ji+1,jj) * zpt_w(ji+1,jj,1) ) * puu(ji,jj,1,Kmm) 
                  zzv = 0.5_wp * ( e1e2t(ji,jj) * zpt_w(ji,jj,1) + e1e2t(ji,jj+1) * zpt_w(ji,jj+1,1) ) * pvv(ji,jj,1,Kmm) 
                  puu(ji,jj,1,Krhs) = puu(ji,jj,1,Krhs) - zzu * r1_e1e2u(ji,jj)   & 
                     &                                        / e3u(ji,jj,1,Kmm) 
                  pvv(ji,jj,1,Krhs) = pvv(ji,jj,1,Krhs) - zzv * r1_e1e2v(ji,jj)   & 
                     &                                        / e3v(ji,jj,1,Kmm) 
               END_2D 
            ENDIF 
         ! 
         ELSE                          !==  Vertical advection  ==! 
            ...
     |-- dynadv_ubs.F90
         SUBROUTINE dyn_adv_ubs( kt, Kbb, Kmm, puu, pvv, Krhs, pau, pav, paw, no_zad ) 
         ...
         IF( PRESENT( no_zad ) ) THEN  !==  No vertical advection  ==!   (except if linear free surface) 
            IF( ln_linssh ) THEN                ! linear free surface: advection through the surface z=0 
               DO_2D( 0, 0, 0, 0 ) 
                  zzu = 0.5_wp * ( e1e2t(ji,jj) * zpt_w(ji,jj,1) + e1e2t(ji+1,jj) * zpt_w(ji+1,jj,1) ) * puu(ji,jj,1,Kmm)
                  zzv = 0.5_wp * ( e1e2t(ji,jj) * zpt_w(ji,jj,1) + e1e2t(ji,jj+1) * zpt_w(ji,jj+1,1) ) * pvv(ji,jj,1,Kmm) 
                  puu(ji,jj,1,Krhs) = puu(ji,jj,1,Krhs) - zzu * r1_e1e2u(ji,jj)   & 
                     &                                        / e3u(ji,jj,1,Kmm) 
                  pvv(ji,jj,1,Krhs) = pvv(ji,jj,1,Krhs) - zzv * r1_e1e2v(ji,jj)   & 
                     &                                        / e3v(ji,jj,1,Kmm) 
               END_2D 
            ENDIF 
         ! 
         ELSE                          !==  Vertical advection  ==! 

Gurvan added a loop optimisation for dynzad.F90

OCE
 |--DYN
     |-- dynzad.F90
All the loops are now gather in a single one.  

Implementation details : barocline processing

r14547 Allow RK3 time-stepping with 2D mode damped.
div_hor interface and sshwzv interface have been changed accordingly for RK3. eos also changed in order to avoid gdep to be used as an input argument in the key_qco framework.

OCE
 |--DYN
     |-- divhor.F90
         SUBROUTINE div_hor_RK3( kt, Kbb, Kmm, puu, pvv, pe3divUh ) 
     |-- sshwzv.F90
         SUBROUTINE wzv_RK3( kt, Kbb, Kmm, Kaa, puu, pvv, pww )
 |--TRA
     |-- eosbn2.F90
         SUBROUTINE eos_insitu_New( pts, Knn, prd ) 

Time step no longer need to be doubled. rk3 routines are added to the code and stprk3 is called through nemogcm when key_RK3 is active.

OCE
 |--DOM
     |-- domain.F90
         #if defined key_RK3 
              rDt   =         rn_Dt 
 	      r1_Dt = 1._wp / rDt
          ...
 |-- nemogcm.F90
     # if defined key_RK3 
             USE stprk3 
     ...
 |-- stprk3.F90
 |-- stprk3-stg.F90

Has been tested and validated against an modified leap frog GYRE in the same configuration with the same namelist.

r14549 Allow RK3 time-stepping with 2D mode.
Prepare forcings and barotropic 2D fields. dynspg_ts remains for 2D mode integration. dyn_vor_RK3 only computes 2D relative vorticity and metric term from 3D to 2D. stp_2D is called by stprk3 in single first.

OCE
 |--DYN
     |-- dynspg_ts.F90
         #remove k_only_ADV
         PUBLIC dyn_drg_init      ! called by rk3ssh
         !  Phase 1 : Coupling between general trend and barotropic estimates (1st step)
         IF( kt == nit000 ) THEN 
 	    IF( .NOT.ln_bt_fw  .OR. ln_bt_av )   CALL ctl_stop( 'dyn_spg_ts: RK3 requires ln_bt_fw=T AND ln_bt_av=F') 
 	 ENDIF
         !                          ! set values computed in RK3_ssh 
 	 zssh_frc(:,:) = sshe_rhs(:,:) 
 	 zu_frc(:,:) =   Ue_rhs(:,:) 
 	 zv_frc(:,:) =   Ve_rhs(:,:) 
 	 zCdU_u  (:,:) = CdU_u   (:,:) 
 	 zCdU_v  (:,:) = CdU_v   (:,:)
         !
 	 IF( kt == nit000 .OR. .NOT. ln_linssh )   CALL dyn_cor_2D_init( Kmm )   ! Set zwz, the barotropic Coriolis force coefficient
         ! Phase 3. update the general trend with the barotropic trend 
         IF(.NOT.ln_bt_av ) THEN                          !* Update Kaa barotropic external mode  
            uu_b(:,:,Kaa) = ua_e  (:,:) 
  	    pvv_b(:,:,Kaa) = va_e  (:,:) 
  	    pssh (:,:,Kaa) = ssha_e(:,:) 
  	 ENDIF
         un_adv...
         ubar...
     |-- dynspg.F90
         #remove k_only_ADV
     |-- dynvor.F90
         SUBROUTINE dyn_vor_3D( kt, Kmm, puu, pvv, Krhs ) 
     |-- dynzdf.F90
         zDt_2 = rDt * 0.5_wp # small cosmetic optim
 |-- stprk3_stg.F90
 |-- stp2d.F90
 |-- stprk3.F90
179	      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
180	      !  RK3 : single first external mode computation
181	      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
182	
183	      CALL stp_2D( kstp, Nbb, Nbb, Naa, Nrhs )   ! out: ssh, (uu_b,vv_b) and (un_adv,vn_adv) at Naa
184	
185	
186	      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
187	      !  RK3 time integration
188	      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
189	
190	      ! Stage 1 :
191	      CALL stp_RK3_stg( 1, kstp, Nbb, Nbb, Nrhs, Naa )
192	      !
193	      Nrhs = Nnn   ;   Nnn  = Naa   ;   Naa  = Nrhs    ! Swap: Nbb unchanged, Nnn <==> Naa
194	      !
195	      ! Stage 2 :
196	      CALL stp_RK3_stg( 2, kstp, Nbb, Nnn, Nrhs, Naa )
197	      !
198	      Nrhs = Nnn   ;   Nnn  = Naa   ;   Naa  = Nrhs    ! Swap: Nbb unchanged, Nnn <==> Naa
199	      !
200	      ! Stage 3 :
201	      CALL stp_RK3_stg( 3, kstp, Nbb, Nnn, Nrhs, Naa )
202	      !
203	      Nrhs = Nbb   ;   Nbb  = Naa   ;   Naa  = Nrhs    ! Swap: Nnn unchanged, Nbb <==> Naa

Implementation of AGRIF with RK3

r14800 introduces the major changes to activate AGRIF with RK3

  • Add provision of ssh data for setting bcs during barotropic loop in agrif_dta_ts subroutine. Indeed, MLF makes use of sshwzv where a first guess of ssh was done and corrected at AGRIF bdys. This routine is not called anymore with RK3.
NST
 |-- agrif_oce_interp.F90
     SUBROUTINE Agrif_dta_ts( kt )
     #if defined key_RK3
        Agrif_SpecialValue    = 0._wp
        Agrif_UseSpecialValue = .TRUE.
        CALL Agrif_Bc_variable(sshn_id, procname=interpsshn )
        Agrif_UseSpecialValue = .FALSE.
     #endif
  • Important change of time indexes on Parent grid in stprk3.F90: "Now" arrays on parent refers to "Nbb" index for RK3 instead of "Nnn" with MLF:
    OCE
     |-- stprk3.F90
         Kbb_a = Nbb; Kmm_a = Nbb; Krhs_a = Nrhs      ! agrif_oce module copies of time level indices
    
  • Added (optional) time interpolation at intermediate stages in Agrif_dyn and Agrif_tra:
    NST
     |-- agrif_oce_interp.F90
          SUBROUTINE Agrif_tra( kt, kstg )
          !!----------------------------------------------------------------------
          !!                  ***  ROUTINE Agrif_tra  ***
          !!----------------------------------------------------------------------
          INTEGER, INTENT(in) ::   kt
          INTEGER, OPTIONAL, INTENT(in) :: kstg
          REAL(wp) :: ztindex
          !
          IF( Agrif_Root() )   RETURN
          !
          ! Set time index depending on stage in case of RK3 time stepping:
          IF ( PRESENT( kstg ) ) THEN
             ztindex = REAL(Agrif_Nbstepint(), wp)
             IF     ( kstg == 1 ) THEN
                ztindex = ztindex + 1._wp / 3._wp
             ELSEIF ( kstg == 2 ) THEN
                ztindex = ztindex + 1._wp / 2._wp
             ELSEIF ( kstg == 3 ) THEN
                ztindex = ztindex + 1._wp
             ENDIF
             ztindex = ztindex / Agrif_Rhot()
          ELSE
             ztindex = REAL(Agrif_Nbstepint()+1, wp) / Agrif_Rhot()
          ENDIF
          !
          Agrif_SpecialValue    = 0._wp
          Agrif_UseSpecialValue = .TRUE.
          l_vremap              = ln_vert_remap
          !
          CALL Agrif_Bc_variable( ts_interp_id, calledweight=ztindex, procname=interptsn )
          !
          Agrif_UseSpecialValue = .FALSE.
          l_vremap              = .FALSE.
          !
       END SUBROUTINE Agrif_tra
    

Functionnality activated in stprk3_stg.F90

OCE
 |-- stprk3_stg.F90
         !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>
         ! Set boundary conditions
         !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<
         !
     # if defined key_agrif
            CALL Agrif_tra( kstp, kstg )             !* AGRIF zoom boundaries
            CALL Agrif_dyn( kstp, kstg )
     # endif
  • Removed updates of Parent "before" fields coming from asselin filtering. cpp directives "#if ! defined key_RK3" have been used in agrif_oce_update.F90 module.
  • Added Agrif sponge trend in barotropic mode (stp2d.F90). It is taken as constant over the barotropic loop, but that's the only source of damping near grid boundaries... Should add time dependent nudging during barotropic loop which could help damping instabilities as reported below without time averaging of barotropic variables.
  • The changes above have also been made for agrif routines related to TOP. At that stage, TOP was nevertheless not functional with RK3.
  • Changes validated (qualitavely) in VORTEX test case. Successful doubling of time step. However results are substantiallly different in term of VORTEX amplitude around grid interface => impact of unchanged adimensionnalized sponge/nudging coefficients ?
  • NB1: I noticed instabilities preventing runs to finish when switching off barotropic time averaging (and using Demange's dissipative time stepping). This occurs also with MLF. Is the periodic data exchange between grids (at baroclinic time step) suitable with such an approach ?
  • NB2: Restartability not checked yet but it is likely that some changes on Agrif time indexes (such as the one reported above) will be needed at initialization.

Solar flux penetration optimization (r14990 start r15083 fully debugged rxxxxx optimized)

Tracer surface boundary condition optimization (r14993)

Ice Shelve now compatible with qco (r15083)

Adapt TOP for RK3

Merge with trunk r15557

Trunk has new management of the halos, RK3 additionnal routines have to be updated accordingly.

  • lbc_lnk_multi routines no longer exist : they have been integrated into lbc_lnk generic routines, then they have to be replaced in :

=> src/OCE/DYN/dynspg_ts.F90
=> src/OCE/stprk3_stg.F90

  • loop have changed and optimized for limiting communications : when relevant RK3 routines will mimic MLF ones

=> src/OCE/DYN/divhor.F90 : div_hor_RK3
=> src/OCE/DYN/sshwzv.F90 : wzv_RK3
=> src/OCE/TRA/trasbc.F90 : tra_sbc_RK3

  • we have optimized tra_qsr routine by limiting intermidiate storing array, computations are now done only in the interior it works for all variables except fraqsr_1lev. Indeed it needs to be defined over the whole domain for the ICE. When not np_BIO fraqsr_1lev depends on qsr_hc, to minimize the code changed I decided to keep qsr_hc defined in the interior and to make a communication on fraqsr_1lev but it may not be the best solution. see with GM !

=> src/OCE/TRA/traqsr.F90 (fraqsr_1lev)

  • src/OCE/stprk3_stg.F90 also has to be updated.

=> A communication is required on r3. Indeed r3. at Kbb and Kmm can be used over the whole domain. In MLF case r3. at Kbb and Kmm are lbc-ised when starting a time step, while in RK3 case because of the stages within a step and r3. at Kmm is never lbc-ised. That is why this communication is required !
=> Advective speeds at Kmm are computed on the whole domain and also required r3u to be defined over the whole domain.
=> As far as I understand ts, tr @ Kaa are not only computed in the interior in order to limit the number of loops, and sometime (ex pt update in src/OCE/TRA/traadv_fct.F90) values are computed but not used. In traadv case pt value outside the interior in erased with a lbc_lnk at the end of the time step. That is why ts/tr have to be initialised over the whole domain. Maybe it should be done at the init only as we discussed with GM !
=> As what has been done for MLF "IF( nn_hls == 2 .AND. l_zdfsh2 ) CALL lbc_lnk( 'stp_RK3_stg', avm_k, 'W', 1.0_wp )" needs to be externalised from the tke routine.

  • rhop removal needs to be adressed properly. For now it has been quickly removed from RK3 but it is required for some DIA routines and over all for tra_mle (activated in ORCA2_ICE_PISCES configuration). The initial target was to compute rhop locally when needed on order to avoid to store a useless rhop array. But is means about 6 times.

=> src/OCE/TRD/trdglo.F90 : glo_dyn_wri changes maye useless since glo_dyn_wri never called !
=> src/OCE/stprk3.F90 rhop@Nbb now computed with rhd at each time step
=> src/OCE/IOM/restart.F90 : remove rhop from restart

  • initialisation with restart sometimes requires Kmm field with are not intialised in RK3, as a matter of simplicity we just copy Kbb into Kmm for ssh, ts, uu, vv fields.

=> src/OCE/IOM/restart.F90 : rst_read
=> src/OCE/IOM/restart.F90 : rst_read_ssh

Documentation updates

Error: Failed to load processor box
No macro or processor named 'box' found

...

Preview

Error: Failed to load processor box
No macro or processor named 'box' found

...

Tests

Error: Failed to load processor box
No macro or processor named 'box' found

Early SETTE tests

Some preliminary SETTE tests have been carried out on branch 2021/dev_r14318_RK3_stage1 at revision 14244. The implementation is not complete at this stage and, in particular, RK3 time-stepping has not yet been implemented for passive tracers. Nevertheless, the tests that are possible will inform on the general status of the branch.

The first step is to enable key_qco and key_RK3 with SETTE. To allow easy selection, the following -Q option was added via changes to sette.sh sette_reference-configurations.sh and sette_test-cases.sh:

  • sette.sh

     
    44MAIN_DIR=$(dirname $SETTE_DIR) 
    55export SETTE_TIMING='no' 
    66export NOT_USING_QCO='no' 
     7export USING_RK3='no' 
    78 
    89# Parse command-line arguments 
    910if [ $# -gt 0 ]; then 
    10   while getopts t:x:cshTq option; do 
     11  while getopts t:x:cshTqQ option; do 
    1112     case $option in 
    1213        c) export SETTE_CLEAN_CONFIGS='yes' 
    1314           export SETTE_SYNC_CONFIGS='yes' 
     
    3637           echo "" 
    3738           echo "key_qco and key_linssh will NOT be activated" 
    3839           echo "";; 
     40       Q) export USING_RK3='yes' 
     41           echo "" 
     42           echo "key_qco and key_RK3 will be activated" 
     43           echo "";; 
    3944        h | *) echo 'sette.sh with no arguments (in this case all configuration will be tested)' 
    4045               echo '-t "CFG1_to_test CFG2_to_test ..." to test some specific configurations' 
    4146               echo '-x "TEST_type TEST_type ..." to specify particular types of test (RESTART is mandatory)' 
  • sette_reference-configurations.sh

     
    143143   export DEL_KEYS="${DEL_KEYS} key_qco key_linssh" 
    144144fi 
    145145# 
     146if [ ${USING_RK3} == "yes" ] 
     147 then 
     148   export ADD_KEYS="${ADD_KEYS} key_qco key_RK3" 
     149fi 
     150# 
    146151# Settings which control the use of stand alone servers (only relevant if using xios) 
    147152# 
    148153export NUM_XIOSERVERS=4 
  • sette_test-cases.sh

     
    140140   export DEL_KEYS="${DEL_KEYS} key_qco key_linssh" 
    141141fi 
    142142# 
     143if [ ${USING_RK3} == "yes" ] 
     144 then 
     145   export ADD_KEYS="${ADD_KEYS} key_qco key_RK3" 
     146fi 
     147# 
    143148# Settings which control the use of stand alone servers (only relevant if using xios) 
    144149# 
    145150export NUM_XIOSERVERS=4 

With these changes and an, otherwise normal, SETTE setup the following tests have been attempted:

sette.sh -Q -t "AMM12 WED025 ICE_AGRIF OVERFLOW LOCK_EXCHANGE VORTEX ISOMIP+"

With the following outcomes:

  • No tests were successful but compilation succeeded and runs started for the following:
    AMM12          -failed both restartability and reproducibility
    OVERFLOW       -failed restartability (no reproducibility: single proc)
    LOCK_EXCHANGE  -failed restartability (last digit differences in Umax)
    
  • Generally there are a few compilation warnings to chase down:
    ftn-7212 crayftn: WARNING STP_2D, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/OVERFLOW_ST/BLD/ppsrc/nemo/stp2d.f90, Line = 175
      Variable "r1_2" is used before it is defined.
    
    ftn-7212 crayftn: WARNING SUB_LOOP_DIA_HSB, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/VORTEX_ST/BLD/ppsrc/nemo/diahsb.f90, Line = 283
      Variable "z_frc_trd_t" is used before it is defined.
    
    ftn-7212 crayftn: WARNING SUB_LOOP_DIA_HSB, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/VORTEX_ST/BLD/ppsrc/nemo/diahsb.f90, Line = 284
      Variable "z_frc_trd_s" is used before it is defined.
    
    ftn-7212 crayftn: WARNING OBS_GRID_SETUP, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/obs_grid.f90, Line = 1275
      Variable "histx1" is used before it is defined.
    
    ftn-7212 crayftn: WARNING OBS_GRID_SETUP, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/obs_grid.f90, Line = 1281
      Variable "histx2" is used before it is defined.
    
    ftn-7212 crayftn: WARNING OBS_GRID_SETUP, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/obs_grid.f90, Line = 1287
    
    ftn-7212 crayftn: WARNING FLO_4RK, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/flo4rk.f90, Line = 85
      Variable "ierror" is used before it is defined.
    
    ftn-7212 crayftn: WARNING ICB_THM, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/icbthm.f90, Line = 218
      Variable "zdvo" is used before it is defined.
    
    ftn-7212 crayftn: WARNING TRA_NPC, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/tranpc.f90, Line = 194
      Variable "klc1" is used before it is defined.
    

None of which appear to be fatal (but the first may be serious)

  • WED025 compiled but failed to run with:
      ===>>> : E R R O R
    
              ===========
    
     dyn_hpg_init : key_qco and ln_hpg_isf not yet compatible
    
  • ICE_AGRIF compiled but failed to run with:
      ===>>> : E R R O R
    
              ===========
    
     STOP
     domain: key_qco and ln_linssh=T or key_linssh are incompatible
    
  • ISOMIP+ failed to compile with:
    ftn-855 crayftn: ERROR STPRK3_STG, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/stprk3_stg.f90, Line = 14, Column = 8
      The compiler has detected errors in module "STPRK3_STG".  No module information file will be created for this module.
    
    
    ftn-389 crayftn: ERROR STP_RK3_STG, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/ISOMIP+_ST/BLD/ppsrc/nemo/stprk3_stg.f90, Line = 203, Column = 12
      No specific match can be found for the generic subprogram call "EOS".
    
  • VORTEX failed to compile with:
    ftn-855 crayftn: ERROR STPRK3_STG, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/VORTEX_ST/BLD/ppsrc/nemo/stprk3_stg.f90, Line = 27, Column = 8
      The compiler has detected errors in module "STPRK3_STG".  No module information file will be created for this module.
    
    
    ftn-297 crayftn: ERROR SUB_LOOP_STP_RK3_STG, File = ../../../lus/cls01095/work/n01/n01/acc/NEMO/2021/dev_r14318_RK3_stage1/tests/VORTEX_ST/BLD/ppsrc/nemo/stprk3_stg.f90, Line = 538, Column = 29
      IMPLICIT NONE is specified in the host scope, therefore an explicit type must be specified for data object "KT".
    

which is associated with the line: CALL Agrif_dyn( kt )

Vortex can be compiled and run with the following (uncommitted) changes:

  • OCE/stp2d.F90

     
    2626   USE sbc_ice , ONLY : snwice_mass, snwice_mass_b 
    2727   USE sbcapr         ! surface boundary condition: atmospheric pressure 
    2828   USE sbcwave,  ONLY : bhd_wave 
     29#if defined key_agrif 
     30   USE agrif_oce_interp 
     31#endif 
    2932 
    3033   PRIVATE 
    3134 
  • OCE/stprk3_stg.F90

     
    354354      ! 
    355355# if defined key_agrif 
    356356            CALL Agrif_tra                     !* AGRIF zoom boundaries 
    357             CALL Agrif_dyn( kt ) 
     357            CALL Agrif_dyn( kstp ) 
    358358# endif 
    359359      !                                        ! local domain boundaries  (T-point, unchanged sign) 
    360360      CALL lbc_lnk_multi( 'stp_RK3_stg', uu(:,:,:,       Kaa), 'U', -1., vv(:,:,:       ,Kaa), 'V', -1.   & 

With these changes it will compile and run but encounters the same restartability and reproducibility errors as the other running tests.

...

Review

Error: Failed to load processor box
No macro or processor named 'box' found

...