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 6092 for branches/2015/dev_agrif_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/step.F90 – NEMO

Ignore:
Timestamp:
2015-12-17T15:19:01+01:00 (9 years ago)
Author:
timgraham
Message:

Merged in trunk at r5518 (branch point of 3.6 stable)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_agrif_v3_6_STABLE/NEMOGCM/NEMO/OPA_SRC/step.F90

    r4980 r6092  
    2424   !!             -   !  2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase + merge TRC-TRA 
    2525   !!            3.4  !  2011-04  (G. Madec, C. Ethe) Merge of dtatem and dtasal 
    26    !!                 !  2012-07  (J. Simeon, G. Madec. C. Ethe) Online coarsening of outputs 
     26   !!                 !  2012-07  (J. Simeon, G. Madec, C. Ethe) Online coarsening of outputs 
     27   !!            3.7  !  2014-04  (F. Roquet, G. Madec) New equations of state 
    2728   !!---------------------------------------------------------------------- 
    2829 
     
    3132   !!---------------------------------------------------------------------- 
    3233   USE step_oce         ! time stepping definition modules 
     34   USE iom 
    3335 
    3436   IMPLICIT NONE 
     
    3941   !! * Substitutions 
    4042#  include "domzgr_substitute.h90" 
    41 #  include "zdfddm_substitute.h90" 
    42    !!---------------------------------------------------------------------- 
    43    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     43!!gm   #  include "zdfddm_substitute.h90" 
     44   !!---------------------------------------------------------------------- 
     45   !! NEMO/OPA 3.7 , NEMO Consortium (2014) 
    4446   !! $Id$ 
    4547   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    8587 
    8688# if defined key_iomput 
    87       IF( Agrif_Nbstepint() == 0 )   CALL iom_swap( "nemo" ) 
     89      IF( Agrif_Nbstepint() == 0 )   CALL iom_swap( cxios_context ) 
    8890# endif 
    8991#endif 
    9092                             indic = 0           ! reset to no error condition 
    9193      IF( kstp == nit000 ) THEN 
    92                       CALL iom_init( "nemo" )      ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
    93          IF( ln_crs ) CALL iom_init( "nemo_crs" )  ! initialize context for coarse grid 
     94         ! must be done after nemo_init for AGRIF+XIOS+OASIS 
     95                      CALL iom_init(      cxios_context          )  ! iom_put initialization 
     96         IF( ln_crs ) CALL iom_init( TRIM(cxios_context)//"_crs" )  ! initialize context for coarse grid 
    9497      ENDIF 
    9598 
    9699      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init) 
    97                              CALL iom_setkt( kstp - nit000 + 1, "nemo"     )   ! say to iom that we are at time step kstp 
    98       IF( ln_crs     )       CALL iom_setkt( kstp - nit000 + 1, "nemo_crs" )   ! say to iom that we are at time step kstp 
     100                             CALL iom_setkt( kstp - nit000 + 1,      cxios_context          )   ! tell iom we are at time step kstp 
     101      IF( ln_crs     )       CALL iom_setkt( kstp - nit000 + 1, TRIM(cxios_context)//"_crs" )   ! tell iom we are at time step kstp 
    99102 
    100103      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    102105      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    103106      IF( lk_tide    )   CALL sbc_tide( kstp ) 
    104       IF( lk_bdy     )   CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    105  
     107      IF( lk_bdy     )  THEN 
     108         IF( ln_apr_dyn) CALL sbc_apr( kstp )   ! bdy_dta needs ssh_ib  
     109                         CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
     110      ENDIF 
    106111                         CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
    107112                                                      ! clem: moved here for bdy ice purpose 
     113      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     114      ! Update stochastic parameters and random T/S fluctuations 
     115      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     116                        CALL sto_par( kstp )          ! Stochastic parameters 
    108117 
    109118      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    110119      ! Ocean physics update                (ua, va, tsa used as workspace) 
    111120      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    112                          CALL bn2( tsb, rn2b )        ! before Brunt-Vaisala frequency 
    113                          CALL bn2( tsn, rn2  )        ! now    Brunt-Vaisala frequency 
     121      !  THERMODYNAMICS 
     122                         CALL eos_rab( tsb, rab_b )       ! before local thermal/haline expension ratio at T-points 
     123                         CALL eos_rab( tsn, rab_n )       ! now    local thermal/haline expension ratio at T-points 
     124                         CALL bn2    ( tsb, rab_b, rn2b ) ! before Brunt-Vaisala frequency 
     125                         CALL bn2    ( tsn, rab_n, rn2  ) ! now    Brunt-Vaisala frequency 
    114126      ! 
    115127      !  VERTICAL PHYSICS 
     
    121133      IF( lk_zdfkpp  )   CALL zdf_kpp( kstp )            ! KPP closure scheme for Kz 
    122134      IF( lk_zdfcst  ) THEN                              ! Constant Kz (reset avt, avm[uv] to the background value) 
    123          avt (:,:,:) = rn_avt0 * tmask(:,:,:) 
    124          avmu(:,:,:) = rn_avm0 * umask(:,:,:) 
    125          avmv(:,:,:) = rn_avm0 * vmask(:,:,:) 
     135         avt (:,:,:) = rn_avt0 * wmask (:,:,:) 
     136         avmu(:,:,:) = rn_avm0 * wumask(:,:,:) 
     137         avmv(:,:,:) = rn_avm0 * wvmask(:,:,:) 
    126138      ENDIF 
    127139      IF( ln_rnf_mouth ) THEN                         ! increase diffusivity at rivers mouths 
     
    144156      ! 
    145157      IF( lk_ldfslp ) THEN                            ! slope of lateral mixing 
    146                          CALL eos( tsb, rhd, gdept_0(:,:,:) )             ! before in situ density 
    147          IF( ln_zps )    CALL zps_hde( kstp, jpts, tsb, gtsu, gtsv,  &    ! Partial steps: before horizontal gradient 
    148             &                                      rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
     158         IF(ln_sto_eos ) CALL sto_pts( tsn )          ! Random T/S fluctuations 
     159                         CALL eos( tsb, rhd, gdept_0(:,:,:) )               ! before in situ density 
     160         IF( ln_zps .AND. .NOT. ln_isfcav)                               & 
     161            &            CALL zps_hde    ( kstp, jpts, tsb, gtsu, gtsv,  &  ! Partial steps: before horizontal gradient 
     162            &                                          rhd, gru , grv    )  ! of t, s, rd at the last ocean level 
     163         IF( ln_zps .AND.       ln_isfcav)                               & 
     164            &            CALL zps_hde_isf( kstp, jpts, tsb, gtsu, gtsv,  &    ! Partial steps for top cell (ISF) 
     165            &                                          rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   & 
     166            &                                   gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi    ) ! of t, s, rd at the first ocean level 
    149167         IF( ln_traldf_grif ) THEN                           ! before slope for Griffies operator 
    150168                         CALL ldf_slp_grif( kstp ) 
     
    156174      IF( lk_traldf_eiv )   CALL ldf_eiv( kstp )      ! eddy induced velocity coefficient 
    157175#endif 
    158 #if defined key_traldf_c3d && key_traldf_smag 
     176#if defined key_traldf_c3d && defined key_traldf_smag 
    159177                          CALL ldf_tra_smag( kstp )      ! eddy induced velocity coefficient 
    160178#  endif 
    161 #if defined key_dynldf_c3d && key_dynldf_smag 
     179#if defined key_dynldf_c3d && defined key_dynldf_smag 
    162180                          CALL ldf_dyn_smag( kstp )      ! eddy induced velocity coefficient 
    163181#  endif 
     
    174192          ! Note that the computation of vertical velocity above, hence "after" sea level 
    175193          ! is necessary to compute momentum advection for the rhs of barotropic loop: 
    176                                   CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) ) ! now in situ density for hpg computation 
    177           IF( ln_zps      )       CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &   ! zps: now hor. derivative 
    178                 &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
     194            IF(ln_sto_eos ) CALL sto_pts( tsn )                             ! Random T/S fluctuations 
     195                            CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) ) ! now in situ density for hpg computation 
     196            IF( ln_zps .AND. .NOT. ln_isfcav)                               & 
     197               &            CALL zps_hde    ( kstp, jpts, tsn, gtsu, gtsv,  &    ! Partial steps: before horizontal gradient 
     198               &                                          rhd, gru , grv    )  ! of t, s, rd at the last ocean level 
     199            IF( ln_zps .AND.       ln_isfcav)                               & 
     200               &            CALL zps_hde_isf( kstp, jpts, tsn, gtsu, gtsv,  &    ! Partial steps for top cell (ISF) 
     201               &                                          rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   & 
     202               &                                   gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi    ) ! of t, s, rd at the last ocean level 
    179203 
    180204                                  ua(:,:,:) = 0.e0             ! set dynamics trends to zero 
     
    205229      ! diagnostics and outputs             (ua, va, tsa used as workspace) 
    206230      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    207       IF( lk_floats  )   CALL flo_stp( kstp )         ! drifting Floats 
    208       IF( lk_diahth  )   CALL dia_hth( kstp )         ! Thermocline depth (20 degres isotherm depth) 
    209       IF( lk_diafwb  )   CALL dia_fwb( kstp )         ! Fresh water budget diagnostics 
    210       IF( ln_diaptr  )   CALL dia_ptr( kstp )         ! Poleward TRansports diagnostics 
    211       IF( lk_diadct  )   CALL dia_dct( kstp )         ! Transports 
    212       IF( lk_diaar5  )   CALL dia_ar5( kstp )         ! ar5 diag 
    213       IF( lk_diaharm )   CALL dia_harm( kstp )        ! Tidal harmonic analysis 
    214                          CALL dia_wri( kstp )         ! ocean model: outputs 
    215       ! 
    216       IF( ln_crs     )   CALL crs_fld( kstp )         ! ocean model: online field coarsening & output 
    217  
     231      IF( lk_floats  )      CALL flo_stp( kstp )         ! drifting Floats 
     232      IF( lk_diahth  )      CALL dia_hth( kstp )         ! Thermocline depth (20 degres isotherm depth) 
     233      IF( .NOT. ln_cpl )    CALL dia_fwb( kstp )         ! Fresh water budget diagnostics 
     234      IF( lk_diadct  )      CALL dia_dct( kstp )         ! Transports 
     235      IF( lk_diaar5  )      CALL dia_ar5( kstp )         ! ar5 diag 
     236      IF( lk_diaharm )      CALL dia_harm( kstp )        ! Tidal harmonic analysis 
     237                            CALL dia_wri( kstp )         ! ocean model: outputs 
     238      ! 
     239      IF( ln_crs     )      CALL crs_fld( kstp )         ! ocean model: online field coarsening & output 
    218240 
    219241#if defined key_top 
     
    223245                         CALL trc_stp( kstp )         ! time-stepping 
    224246#endif 
     247 
    225248 
    226249      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    240263      IF( lk_zdfkpp      )   CALL tra_kpp    ( kstp )       ! KPP non-local tracer fluxes 
    241264                             CALL tra_ldf    ( kstp )       ! lateral mixing 
     265 
     266      IF( ln_diaptr      )   CALL dia_ptr                   ! Poleward adv/ldf TRansports diagnostics 
     267 
    242268#if defined key_agrif 
    243269      IF(.NOT. Agrif_Root()) CALL Agrif_Sponge_tra          ! tracers sponge 
     
    248274         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
    249275                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
     276            IF( ln_sto_eos ) CALL sto_pts( tsn )                 ! Random T/S fluctuations 
    250277                             CALL eos    ( tsa, rhd, rhop, fsdept_n(:,:,:) )  ! Time-filtered in situ density for hpg computation 
    251          IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsa, gtsu, gtsv,  &    ! zps: time filtered hor. derivative 
    252             &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
    253  
     278            IF( ln_zps .AND. .NOT. ln_isfcav)                                & 
     279               &             CALL zps_hde    ( kstp, jpts, tsa, gtsu, gtsv,  &    ! Partial steps: before horizontal gradient 
     280               &                                           rhd, gru , grv    )  ! of t, s, rd at the last ocean level 
     281            IF( ln_zps .AND.       ln_isfcav)                                & 
     282               &             CALL zps_hde_isf( kstp, jpts, tsa, gtsu, gtsv,  &    ! Partial steps for top cell (ISF) 
     283               &                                           rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   & 
     284               &                                    gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi    ) ! of t, s, rd at the last ocean level 
    254285      ELSE                                                  ! centered hpg  (eos then time stepping) 
    255286         IF ( .NOT. lk_dynspg_ts ) THEN                     ! eos already called in time-split case 
    256                                 CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )  ! now in situ density for hpg computation 
    257             IF( ln_zps      )   CALL zps_hde( kstp, jpts, tsn, gtsu, gtsv,  &    ! zps: now hor. derivative 
    258             &                                          rhd, gru , grv  )      ! of t, s, rd at the last ocean level 
     287            IF( ln_sto_eos ) CALL sto_pts( tsn )    ! Random T/S fluctuations 
     288                             CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )  ! now in situ density for hpg computation 
     289         IF( ln_zps .AND. .NOT. ln_isfcav)                                   & 
     290               &             CALL zps_hde    ( kstp, jpts, tsn, gtsu, gtsv,  &    ! Partial steps: before horizontal gradient 
     291               &                                           rhd, gru , grv    )  ! of t, s, rd at the last ocean level 
     292         IF( ln_zps .AND.       ln_isfcav)                                   &  
     293               &             CALL zps_hde_isf( kstp, jpts, tsn, gtsu, gtsv,  &    ! Partial steps for top cell (ISF) 
     294               &                                           rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   & 
     295               &                                    gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi    ) ! of t, s, rd at the last ocean level 
    259296         ENDIF 
    260297         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
     
    330367                 CALL iom_close( numror )     ! close input  ocean restart file 
    331368         IF(lwm) CALL FLUSH    ( numond )     ! flush output namelist oce 
    332          IF(lwm) CALL FLUSH    ( numoni )     ! flush output namelist ice     
    333       ENDIF 
    334  
    335       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    336       ! Trends                              (ua, va, tsa used as workspace) 
    337       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    338       IF( nstop == 0 ) THEN 
    339          IF( lk_trddyn     )   CALL trd_dwr( kstp )         ! trends: dynamics 
    340          IF( lk_trdtra     )   CALL trd_twr( kstp )         ! trends: active tracers 
    341          IF( lk_trdmld     )   CALL trd_mld( kstp )         ! trends: Mixed-layer 
    342          IF( lk_trdvor     )   CALL trd_vor( kstp )         ! trends: vorticity budget 
     369         IF( lwm.AND.numoni /= -1 ) CALL FLUSH    ( numoni )     ! flush output namelist ice 
    343370      ENDIF 
    344371 
     
    346373      ! Coupled mode 
    347374      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    348       IF( lk_cpl           )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
     375      IF( lk_oasis         )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    349376      ! 
    350377#if defined key_iomput 
    351378      IF( kstp == nitend .OR. indic < 0 ) THEN  
    352                       CALL iom_context_finalize( "nemo"     ) ! needed for XIOS+AGRIF 
    353          IF( ln_crs ) CALL iom_context_finalize( "nemo_crs" ) !  
     379                      CALL iom_context_finalize(      cxios_context          ) ! needed for XIOS+AGRIF 
     380         IF( ln_crs ) CALL iom_context_finalize( trim(cxios_context)//"_crs" ) !  
    354381      ENDIF 
    355382#endif 
Note: See TracChangeset for help on using the changeset viewer.