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 13463 for NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/step.F90 – NEMO

Ignore:
Timestamp:
2020-09-14T17:40:34+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2195:update to trunk 13461

Location:
NEMO/branches/2019/dev_r11351_fldread_with_XIOS
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@13382        sette 
  • NEMO/branches/2019/dev_r11351_fldread_with_XIOS/src/OCE/step.F90

    r11405 r13463  
    3131   !!             -   !  2015-11  (J. Chanut) free surface simplification (remove filtered free surface) 
    3232   !!            4.0  !  2017-05  (G. Madec)  introduction of the vertical physics manager (zdfphy) 
    33    !!---------------------------------------------------------------------- 
    34  
     33   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme 
     34   !!---------------------------------------------------------------------- 
     35#if defined key_qco 
     36   !!---------------------------------------------------------------------- 
     37   !!   'key_qco'      EMPTY MODULE      Quasi-Eulerian vertical coordonate 
     38   !!---------------------------------------------------------------------- 
     39#else 
    3540   !!---------------------------------------------------------------------- 
    3641   !!   stp             : OPA system time-stepping 
     
    4449 
    4550   PUBLIC   stp   ! called by nemogcm.F90 
     51 
     52   !!---------------------------------------------------------------------- 
     53   !! time level indices 
     54   !!---------------------------------------------------------------------- 
     55   INTEGER, PUBLIC :: Nbb, Nnn, Naa, Nrhs          !! used by nemo_init 
    4656 
    4757   !!---------------------------------------------------------------------- 
     
    7686      !!---------------------------------------------------------------------- 
    7787      INTEGER ::   ji, jj, jk   ! dummy loop indice 
    78       INTEGER ::   indic        ! error indicator if < 0 
    7988!!gm kcall can be removed, I guess 
    8089      INTEGER ::   kcall        ! optional integer argument (dom_vvl_sf_nxt) 
    8190      !! --------------------------------------------------------------------- 
    8291#if defined key_agrif 
     92      IF( nstop > 0 ) RETURN   ! avoid to go further if an error was detected during previous time step (child grid) 
    8393      kstp = nit000 + Agrif_Nb_Step() 
     94      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    8495      IF( lk_agrif_debug ) THEN 
    8596         IF( Agrif_Root() .and. lwp)   WRITE(*,*) '---' 
     
    95106      ! 
    96107      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     108      ! model timestep 
     109      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     110      ! 
     111      IF( l_1st_euler ) THEN   
     112         ! start or restart with Euler 1st time-step 
     113         rDt =  rn_Dt    
     114         r1_Dt = 1._wp / rDt 
     115      ENDIF 
     116      ! 
     117      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    97118      ! update I/O and calendar  
    98119      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    99                              indic = 0                ! reset to no error condition 
    100                               
    101120      IF( kstp == nit000 ) THEN                       ! initialize IOM context (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    102                              CALL iom_init(      cxios_context          )  ! for model grid (including passible AGRIF zoom) 
     121                             CALL iom_init( cxios_context, ld_closedef=.FALSE. )   ! for model grid (including possible AGRIF zoom) 
     122         IF( lk_diamlr   )   CALL dia_mlr_iom_init    ! with additional setup for multiple-linear-regression analysis 
     123                             CALL iom_init_closedef 
    103124         IF( ln_crs      )   CALL iom_init( TRIM(cxios_context)//"_crs" )  ! for coarse grid 
    104125      ENDIF 
     
    108129 
    109130      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    110       ! Update external forcing (tides, open boundaries, and surface boundary condition (including sea-ice) 
    111       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    112       IF( ln_tide    )   CALL sbc_tide( kstp )                   ! update tide potential 
    113       IF( ln_apr_dyn )   CALL sbc_apr ( kstp )                   ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib)  
    114       IF( ln_bdy     )   CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    115                          CALL sbc     ( kstp )                   ! Sea Boundary Condition (including sea-ice) 
     131      ! Update external forcing (tides, open boundaries, ice shelf interaction and surface boundary condition (including sea-ice) 
     132      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     133      IF( ln_tide    )   CALL tide_update( kstp )                     ! update tide potential 
     134      IF( ln_apr_dyn )   CALL sbc_apr ( kstp )                        ! atmospheric pressure (NB: call before bdy_dta which needs ssh_ib)  
     135      IF( ln_bdy     )   CALL bdy_dta ( kstp, Nnn )                   ! update dynamic & tracer data at open boundaries 
     136      IF( ln_isf     )   CALL isf_stp ( kstp, Nnn ) 
     137                         CALL sbc     ( kstp, Nbb, Nnn )              ! Sea Boundary Condition (including sea-ice) 
    116138 
    117139      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    119141      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    120142      IF( ln_sto_eos ) CALL sto_par( kstp )          ! Stochastic parameters 
    121       IF( ln_sto_eos ) CALL sto_pts( tsn  )          ! Random T/S fluctuations 
     143      IF( ln_sto_eos ) CALL sto_pts( ts(:,:,:,:,Nnn)  )          ! Random T/S fluctuations 
    122144 
    123145      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    125147      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    126148      !  THERMODYNAMICS 
    127                          CALL eos_rab( tsb, rab_b )       ! before local thermal/haline expension ratio at T-points 
    128                          CALL eos_rab( tsn, rab_n )       ! now    local thermal/haline expension ratio at T-points 
    129                          CALL bn2    ( tsb, rab_b, rn2b ) ! before Brunt-Vaisala frequency 
    130                          CALL bn2    ( tsn, rab_n, rn2  ) ! now    Brunt-Vaisala frequency 
     149                         CALL eos_rab( ts(:,:,:,:,Nbb), rab_b, Nnn )       ! before local thermal/haline expension ratio at T-points 
     150                         CALL eos_rab( ts(:,:,:,:,Nnn), rab_n, Nnn )       ! now    local thermal/haline expension ratio at T-points 
     151                         CALL bn2    ( ts(:,:,:,:,Nbb), rab_b, rn2b, Nnn ) ! before Brunt-Vaisala frequency 
     152                         CALL bn2    ( ts(:,:,:,:,Nnn), rab_n, rn2, Nnn  ) ! now    Brunt-Vaisala frequency 
    131153 
    132154      !  VERTICAL PHYSICS 
    133                          CALL zdf_phy( kstp )         ! vertical physics update (top/bot drag, avt, avs, avm + MLD) 
     155                         CALL zdf_phy( kstp, Nbb, Nnn, Nrhs )   ! vertical physics update (top/bot drag, avt, avs, avm + MLD) 
    134156 
    135157      !  LATERAL  PHYSICS 
    136158      ! 
    137159      IF( l_ldfslp ) THEN                             ! slope of lateral mixing 
    138                          CALL eos( tsb, rhd, gdept_0(:,:,:) )               ! before in situ density 
    139  
    140          IF( ln_zps .AND. .NOT. ln_isfcav)                               & 
    141             &            CALL zps_hde    ( kstp, jpts, tsb, gtsu, gtsv,  &  ! Partial steps: before horizontal gradient 
    142             &                                          rhd, gru , grv    )  ! of t, s, rd at the last ocean level 
    143  
    144          IF( ln_zps .AND.       ln_isfcav)                               & 
    145             &            CALL zps_hde_isf( kstp, jpts, tsb, gtsu, gtsv, gtui, gtvi,  &  ! Partial steps for top cell (ISF) 
    146             &                                          rhd, gru , grv , grui, grvi   )  ! of t, s, rd at the first ocean level 
     160                         CALL eos( ts(:,:,:,:,Nbb), rhd, gdept_0(:,:,:) )               ! before in situ density 
     161 
     162         IF( ln_zps .AND. .NOT. ln_isfcav)                                    & 
     163            &            CALL zps_hde    ( kstp, Nnn, jpts, ts(:,:,:,:,Nbb), gtsu, gtsv,  &  ! Partial steps: before horizontal gradient 
     164            &                                          rhd, gru , grv    )       ! of t, s, rd at the last ocean level 
     165 
     166         IF( ln_zps .AND.       ln_isfcav)                                                & 
     167            &            CALL zps_hde_isf( kstp, Nnn, jpts, ts(:,:,:,:,Nbb), gtsu, gtsv, gtui, gtvi,  &  ! Partial steps for top cell (ISF) 
     168            &                                          rhd, gru , grv , grui, grvi   )       ! of t, s, rd at the first ocean level 
    147169         IF( ln_traldf_triad ) THEN  
    148                          CALL ldf_slp_triad( kstp )                       ! before slope for triad operator 
     170                         CALL ldf_slp_triad( kstp, Nbb, Nnn )             ! before slope for triad operator 
    149171         ELSE      
    150                          CALL ldf_slp     ( kstp, rhd, rn2b )             ! before slope for standard operator 
     172                         CALL ldf_slp     ( kstp, rhd, rn2b, Nbb, Nnn )   ! before slope for standard operator 
    151173         ENDIF 
    152174      ENDIF 
    153       !                                                                   ! eddy diffusivity coeff. 
    154       IF( l_ldftra_time .OR. l_ldfeiv_time )   CALL ldf_tra( kstp )       !       and/or eiv coeff. 
    155       IF( l_ldfdyn_time                    )   CALL ldf_dyn( kstp )       ! eddy viscosity coeff.  
     175      !                                                                        ! eddy diffusivity coeff. 
     176      IF( l_ldftra_time .OR. l_ldfeiv_time )   CALL ldf_tra( kstp, Nbb, Nnn )  !       and/or eiv coeff. 
     177      IF( l_ldfdyn_time                    )   CALL ldf_dyn( kstp, Nbb )       ! eddy viscosity coeff.  
    156178 
    157179      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    159181      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    160182 
    161                             CALL ssh_nxt       ( kstp )  ! after ssh (includes call to div_hor) 
    162       IF( .NOT.ln_linssh )  CALL dom_vvl_sf_nxt( kstp )  ! after vertical scale factors  
    163                             CALL wzv           ( kstp )  ! now cross-level velocity  
    164       IF( ln_zad_Aimp )     CALL wAimp         ( kstp )  ! Adaptive-implicit vertical advection partitioning 
    165                             CALL eos    ( tsn, rhd, rhop, gdept_n(:,:,:) )  ! now in situ density for hpg computation 
     183                            CALL ssh_nxt       ( kstp, Nbb, Nnn, ssh, Naa )    ! after ssh (includes call to div_hor) 
     184      IF( .NOT.ln_linssh )  CALL dom_vvl_sf_nxt( kstp, Nbb, Nnn,      Naa )    ! after vertical scale factors  
     185                            CALL wzv           ( kstp, Nbb, Nnn, Naa, ww  )    ! now cross-level velocity  
     186      IF( ln_zad_Aimp )     CALL wAimp         ( kstp,      Nnn          )  ! Adaptive-implicit vertical advection partitioning 
     187                            CALL eos    ( ts(:,:,:,:,Nnn), rhd, rhop, gdept(:,:,:,Nnn) )  ! now in situ density for hpg computation 
    166188                             
    167 !!jc: fs simplification 
    168 !!jc: lines below are useless if ln_linssh=F. Keep them here (which maintains a bug if ln_linssh=T and ln_zps=T, cf ticket #1636)  
    169 !!                                         but ensures reproductible results 
    170 !!                                         with previous versions using split-explicit free surface           
    171             IF( ln_zps .AND. .NOT. ln_isfcav )                               & 
    172                &            CALL zps_hde    ( kstp, jpts, tsn, gtsu, gtsv,   &  ! Partial steps: before horizontal gradient 
    173                &                                          rhd, gru , grv     )  ! of t, s, rd at the last ocean level 
    174             IF( ln_zps .AND.       ln_isfcav )                                          & 
    175                &            CALL zps_hde_isf( kstp, jpts, tsn, gtsu, gtsv, gtui, gtvi,  &  ! Partial steps for top cell (ISF) 
    176                &                                          rhd, gru , grv , grui, grvi   )  ! of t, s, rd at the first ocean level 
    177 !!jc: fs simplification 
    178189                             
    179                          ua(:,:,:) = 0._wp            ! set dynamics trends to zero 
    180                          va(:,:,:) = 0._wp 
     190                         uu(:,:,:,Nrhs) = 0._wp            ! set dynamics trends to zero 
     191                         vv(:,:,:,Nrhs) = 0._wp 
    181192 
    182193      IF(  lk_asminc .AND. ln_asmiau .AND. ln_dyninc )   & 
    183                &         CALL dyn_asm_inc   ( kstp )  ! apply dynamics assimilation increment 
    184       IF( ln_bdy     )   CALL bdy_dyn3d_dmp ( kstp )  ! bdy damping trends 
     194               &         CALL dyn_asm_inc   ( kstp, Nbb, Nnn, uu, vv, Nrhs )  ! apply dynamics assimilation increment 
     195      IF( ln_bdy     )   CALL bdy_dyn3d_dmp ( kstp, Nbb,      uu, vv, Nrhs )  ! bdy damping trends 
    185196#if defined key_agrif 
    186197      IF(.NOT. Agrif_Root())  &  
    187198               &         CALL Agrif_Sponge_dyn        ! momentum sponge 
    188199#endif 
    189                          CALL dyn_adv       ( kstp )  ! advection (vector or flux form) 
    190                          CALL dyn_vor       ( kstp )  ! vorticity term including Coriolis 
    191                          CALL dyn_ldf       ( kstp )  ! lateral mixing 
    192       IF( ln_zdfosm  )   CALL dyn_osm       ( kstp )  ! OSMOSIS non-local velocity fluxes 
    193                          CALL dyn_hpg       ( kstp )  ! horizontal gradient of Hydrostatic pressure 
    194                          CALL dyn_spg       ( kstp )  ! surface pressure gradient 
    195  
    196                                                       ! With split-explicit free surface, since now transports have been updated and ssha as well 
     200                         CALL dyn_adv( kstp, Nbb, Nnn      , uu, vv, Nrhs )  ! advection (VF or FF)   ==> RHS 
     201                         CALL dyn_vor( kstp,      Nnn      , uu, vv, Nrhs )  ! vorticity              ==> RHS 
     202                         CALL dyn_ldf( kstp, Nbb, Nnn      , uu, vv, Nrhs )  ! lateral mixing 
     203      IF( ln_zdfosm  )   CALL dyn_osm( kstp,      Nnn      , uu, vv, Nrhs )  ! OSMOSIS non-local velocity fluxes ==> RHS 
     204                         CALL dyn_hpg( kstp,      Nnn      , uu, vv, Nrhs )  ! horizontal gradient of Hydrostatic pressure 
     205                         CALL dyn_spg( kstp, Nbb, Nnn, Nrhs, uu, vv, ssh, uu_b, vv_b, Naa )  ! surface pressure gradient 
     206 
     207                                                      ! With split-explicit free surface, since now transports have been updated and ssh(:,:,Nrhs) as well 
    197208      IF( ln_dynspg_ts ) THEN                         ! vertical scale factors and vertical velocity need to be updated 
    198                             CALL div_hor    ( kstp )              ! Horizontal divergence  (2nd call in time-split case) 
    199          IF(.NOT.ln_linssh) CALL dom_vvl_sf_nxt( kstp, kcall=2 )  ! after vertical scale factors (update depth average component) 
    200       ENDIF 
    201                          CALL dyn_zdf       ( kstp )  ! vertical diffusion 
    202  
    203       IF( ln_dynspg_ts ) THEN                         
    204                             CALL wzv        ( kstp )              ! now cross-level velocity  
    205          IF( ln_zad_Aimp )  CALL wAimp      ( kstp )  ! Adaptive-implicit vertical advection partitioning 
    206       ENDIF 
     209                            CALL div_hor       ( kstp, Nbb, Nnn )                ! Horizontal divergence  (2nd call in time-split case) 
     210         IF(.NOT.ln_linssh) CALL dom_vvl_sf_nxt( kstp, Nbb, Nnn, Naa, kcall=2 )  ! after vertical scale factors (update depth average component) 
     211      ENDIF 
     212                            CALL dyn_zdf    ( kstp, Nbb, Nnn, Nrhs, uu, vv, Naa )  ! vertical diffusion 
     213      IF( ln_dynspg_ts ) THEN                                                       ! vertical scale factors and vertical velocity need to be updated 
     214                            CALL wzv        ( kstp, Nbb, Nnn, Naa, ww )             ! now cross-level velocity  
     215         IF( ln_zad_Aimp )  CALL wAimp      ( kstp,      Nnn )                      ! Adaptive-implicit vertical advection partitioning 
     216      ENDIF 
     217       
    207218 
    208219      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    209220      ! cool skin 
    210221      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
    211       IF ( ln_diurnal )  CALL stp_diurnal( kstp ) 
     222      IF ( ln_diurnal )  CALL diurnal_layers( kstp ) 
    212223       
    213224      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    214225      ! diagnostics and outputs 
    215226      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    216       IF( lk_floats  )   CALL flo_stp ( kstp )        ! drifting Floats 
    217       IF( ln_diacfl  )   CALL dia_cfl ( kstp )        ! Courant number diagnostics 
    218       IF( lk_diahth  )   CALL dia_hth ( kstp )        ! Thermocline depth (20 degres isotherm depth) 
    219       IF( lk_diadct  )   CALL dia_dct ( kstp )        ! Transports 
    220                          CALL dia_ar5 ( kstp )        ! ar5 diag 
    221       IF( lk_diaharm )   CALL dia_harm( kstp )        ! Tidal harmonic analysis 
    222                          CALL dia_wri ( kstp )        ! ocean model: outputs 
    223       ! 
    224       IF( ln_crs     )   CALL crs_fld       ( kstp )  ! ocean model: online field coarsening & output 
     227      IF( ln_floats  )   CALL flo_stp   ( kstp, Nbb, Nnn )      ! drifting Floats 
     228      IF( ln_diacfl  )   CALL dia_cfl   ( kstp,      Nnn )      ! Courant number diagnostics 
     229                         CALL dia_hth   ( kstp,      Nnn )      ! Thermocline depth (20 degres isotherm depth) 
     230      IF( ln_diadct  )   CALL dia_dct   ( kstp,      Nnn )      ! Transports 
     231                         CALL dia_ar5   ( kstp,      Nnn )      ! ar5 diag 
     232                         CALL dia_ptr   ( kstp,      Nnn )      ! Poleward adv/ldf TRansports diagnostics 
     233                         CALL dia_wri   ( kstp,      Nnn )      ! ocean model: outputs 
     234      IF( ln_crs     )   CALL crs_fld   ( kstp,      Nnn )      ! ocean model: online field coarsening & output 
     235      IF( lk_diadetide ) CALL dia_detide( kstp )                ! Weights computation for daily detiding of model diagnostics 
     236      IF( lk_diamlr  )   CALL dia_mlr                           ! Update time used in multiple-linear-regression analysis 
    225237       
    226238#if defined key_top 
     
    228240      ! Passive Tracer Model 
    229241      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    230                          CALL trc_stp       ( kstp )  ! time-stepping 
     242                         CALL trc_stp       ( kstp, Nbb, Nnn, Nrhs, Naa )  ! time-stepping 
    231243#endif 
    232244 
     
    234246      ! Active tracers                               
    235247      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    236                          tsa(:,:,:,:) = 0._wp         ! set tracer trends to zero 
     248                         ts(:,:,:,:,Nrhs) = 0._wp         ! set tracer trends to zero 
    237249 
    238250      IF(  lk_asminc .AND. ln_asmiau .AND. & 
    239          & ln_trainc )   CALL tra_asm_inc   ( kstp )  ! apply tracer assimilation increment 
    240                          CALL tra_sbc       ( kstp )  ! surface boundary condition 
    241       IF( ln_traqsr  )   CALL tra_qsr       ( kstp )  ! penetrative solar radiation qsr 
    242       IF( ln_trabbc  )   CALL tra_bbc       ( kstp )  ! bottom heat flux 
    243       IF( ln_trabbl  )   CALL tra_bbl       ( kstp )  ! advective (and/or diffusive) bottom boundary layer scheme 
    244       IF( ln_tradmp  )   CALL tra_dmp       ( kstp )  ! internal damping trends 
    245       IF( ln_bdy     )   CALL bdy_tra_dmp   ( kstp )  ! bdy damping trends 
     251         & ln_trainc )   CALL tra_asm_inc( kstp, Nbb, Nnn, ts, Nrhs )  ! apply tracer assimilation increment 
     252                         CALL tra_sbc    ( kstp,      Nnn, ts, Nrhs )  ! surface boundary condition 
     253      IF( ln_traqsr  )   CALL tra_qsr    ( kstp,      Nnn, ts, Nrhs )  ! penetrative solar radiation qsr 
     254      IF( ln_isf     )   CALL tra_isf    ( kstp,      Nnn, ts, Nrhs )  ! ice shelf heat flux 
     255      IF( ln_trabbc  )   CALL tra_bbc    ( kstp,      Nnn, ts, Nrhs )  ! bottom heat flux 
     256      IF( ln_trabbl  )   CALL tra_bbl    ( kstp, Nbb, Nnn, ts, Nrhs )  ! advective (and/or diffusive) bottom boundary layer scheme 
     257      IF( ln_tradmp  )   CALL tra_dmp    ( kstp, Nbb, Nnn, ts, Nrhs )  ! internal damping trends 
     258      IF( ln_bdy     )   CALL bdy_tra_dmp( kstp, Nbb,      ts, Nrhs )  ! bdy damping trends 
    246259#if defined key_agrif 
    247260      IF(.NOT. Agrif_Root())  &  
    248261               &         CALL Agrif_Sponge_tra        ! tracers sponge 
    249262#endif 
    250                          CALL tra_adv       ( kstp )  ! horizontal & vertical advection 
    251       IF( ln_zdfosm  )   CALL tra_osm       ( kstp )  ! OSMOSIS non-local tracer fluxes 
     263                         CALL tra_adv    ( kstp, Nbb, Nnn, ts, Nrhs )  ! hor. + vert. advection ==> RHS 
     264      IF( ln_zdfosm  )   CALL tra_osm    ( kstp,      Nnn, ts, Nrhs )  ! OSMOSIS non-local tracer fluxes ==> RHS 
    252265      IF( lrst_oce .AND. ln_zdfosm ) & 
    253            &             CALL osm_rst( kstp, 'WRITE' )! write OSMOSIS outputs + wn (so must do here) to restarts 
    254                          CALL tra_ldf       ( kstp )  ! lateral mixing 
    255  
    256 !!gm : why CALL to dia_ptr has been moved here??? (use trends info?) 
    257       IF( ln_diaptr  )   CALL dia_ptr                 ! Poleward adv/ldf TRansports diagnostics 
    258 !!gm 
    259                          CALL tra_zdf       ( kstp )  ! vertical mixing and after tracer fields 
    260       IF( ln_zdfnpc  )   CALL tra_npc       ( kstp )  ! update after fields by non-penetrative convection 
    261  
    262       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    263       ! Set boundary conditions and Swap 
     266           &             CALL osm_rst    ( kstp,      Nnn, 'WRITE'  )  ! write OSMOSIS outputs + ww (so must do here) to restarts 
     267                         CALL tra_ldf    ( kstp, Nbb, Nnn, ts, Nrhs )  ! lateral mixing 
     268 
     269                         CALL tra_zdf    ( kstp, Nbb, Nnn, Nrhs, ts, Naa  )  ! vertical mixing and after tracer fields 
     270      IF( ln_zdfnpc  )   CALL tra_npc    ( kstp,      Nnn, Nrhs, ts, Naa  )  ! update after fields by non-penetrative convection 
     271 
     272      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     273      ! Set boundary conditions, time filter and swap time levels 
    264274      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    265275!!jc1: For agrif, it would be much better to finalize tracers/momentum here (e.g. bdy conditions) and move the swap  
     
    276286!!    place. 
    277287!!  
    278 !!jc2: dynnxt must be the latest call. e3t_b are indeed updated in that routine 
    279                          CALL tra_nxt       ( kstp )  ! finalize (bcs) tracer fields at next time step and swap 
    280                          CALL dyn_nxt       ( kstp )  ! finalize (bcs) velocities at next time step and swap (always called after tra_nxt) 
    281                          CALL ssh_swp       ( kstp )  ! swap of sea surface height 
    282       IF(.NOT.ln_linssh) CALL dom_vvl_sf_swp( kstp )  ! swap of vertical scale factors 
    283       ! 
    284       IF( ln_diahsb  )   CALL dia_hsb       ( kstp )  ! - ML - global conservation diagnostics 
     288!!jc2: dynnxt must be the latest call. e3t(:,:,:,Nbb) are indeed updated in that routine 
     289                         CALL tra_atf       ( kstp, Nbb, Nnn, Naa, ts )                      ! time filtering of "now" tracer arrays 
     290                         CALL dyn_atf       ( kstp, Nbb, Nnn, Naa, uu, vv, e3t, e3u, e3v  )  ! time filtering of "now" velocities and scale factors 
     291                         CALL ssh_atf       ( kstp, Nbb, Nnn, Naa, ssh )                     ! time filtering of "now" sea surface height 
     292      ! 
     293      ! Swap time levels 
     294      Nrhs = Nbb 
     295      Nbb = Nnn 
     296      Nnn = Naa 
     297      Naa = Nrhs 
     298      ! 
     299      IF(.NOT.ln_linssh) CALL dom_vvl_sf_update( kstp, Nbb, Nnn, Naa )  ! recompute vertical scale factors 
     300      ! 
     301      IF( ln_diahsb  )   CALL dia_hsb       ( kstp, Nbb, Nnn )  ! - ML - global conservation diagnostics 
    285302 
    286303!!gm : This does not only concern the dynamics ==>>> add a new title 
     
    289306!!jc: That would be better, but see comment above 
    290307!! 
    291       IF( lrst_oce   )   CALL rst_write    ( kstp )   ! write output ocean restart file 
     308      IF( lrst_oce   )   CALL rst_write    ( kstp, Nbb, Nnn )   ! write output ocean restart file 
    292309      IF( ln_sto_eos )   CALL sto_rst_write( kstp )   ! write restart file for stochastic parameters 
    293310 
    294311#if defined key_agrif 
    295312      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    296       ! AGRIF 
     313      ! AGRIF recursive integration 
    297314      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
    298                          CALL Agrif_Integrate_ChildGrids( stp )  ! allows to finish all the Child Grids before updating 
    299  
    300                          IF( Agrif_NbStepint() == 0 ) CALL Agrif_update_all( ) ! Update all components 
    301 #endif 
    302       IF( ln_diaobs  )   CALL dia_obs      ( kstp )      ! obs-minus-model (assimilation) diagnostics (call after dynamics update) 
    303  
     315                         Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs      ! agrif_oce module copies of time level indices 
     316                         CALL Agrif_Integrate_ChildGrids( stp )       ! allows to finish all the Child Grids before updating 
     317 
     318#endif 
    304319      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    305320      ! Control 
    306321      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    307                          CALL stp_ctl      ( kstp, indic ) 
    308                           
     322                         CALL stp_ctl      ( kstp, Nnn ) 
     323 
     324#if defined key_agrif 
     325      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     326      ! AGRIF update 
     327      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
     328      IF( Agrif_NbStepint() == 0 .AND. nstop == 0 ) THEN 
     329                         CALL Agrif_update_all( )                  ! Update all components 
     330      ENDIF 
     331 
     332#endif 
     333      IF( ln_diaobs .AND. nstop == 0 )  CALL dia_obs( kstp, Nnn )  ! obs-minus-model (assimilation) diags (after dynamics update) 
     334 
     335      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     336      ! File manipulation at the end of the first time step 
     337      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<                          
    309338      IF( kstp == nit000 ) THEN                          ! 1st time step only 
    310339                                        CALL iom_close( numror )   ! close input  ocean restart file 
     
    316345      ! Coupled mode 
    317346      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    318 !!gm why lk_oasis and not lk_cpl ???? 
    319       IF( lk_oasis   )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
     347      IF( lk_oasis .AND. nstop == 0 )   CALL sbc_cpl_snd( kstp, Nbb, Nnn )     ! coupled mode : field exchanges 
    320348      ! 
    321349#if defined key_iomput 
    322       IF( kstp == nitend .OR. indic < 0 ) THEN  
     350      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     351      ! Finalize contextes if end of simulation or error detected 
     352      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<                          
     353      IF( kstp == nitend .OR. nstop > 0 ) THEN  
    323354                      CALL iom_context_finalize(      cxios_context          ) ! needed for XIOS+AGRIF 
    324                       IF(lrxios) CALL iom_context_finalize(      crxios_context          ) 
     355         IF( lrxios ) CALL iom_context_finalize(      crxios_context         ) 
    325356                      IF(lxios_blkw) CALL iom_context_finalize(  cbwxios_context         ) 
    326357         IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !  
     
    328359#endif 
    329360      ! 
     361      IF( l_1st_euler ) THEN         ! recover Leap-frog timestep 
     362         rDt = 2._wp * rn_Dt    
     363         r1_Dt = 1._wp / rDt 
     364         l_1st_euler = .FALSE.       
     365      ENDIF 
     366      ! 
    330367      IF( ln_timing )   CALL timing_stop('stp') 
    331368      ! 
    332369   END SUBROUTINE stp 
    333     
     370   ! 
     371#endif 
    334372   !!====================================================================== 
    335373END MODULE step 
Note: See TracChangeset for help on using the changeset viewer.