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 9987 for branches/UKMO/dev_r5518_obs_oper_update_icethick/NEMOGCM/NEMO/OPA_SRC/step.F90 – NEMO

Ignore:
Timestamp:
2018-07-23T11:33:03+02:00 (6 years ago)
Author:
emmafiedler
Message:

Merge with GO6 FOAMv14 package branch r9288

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_obs_oper_update_icethick/NEMOGCM/NEMO/OPA_SRC/step.F90

    r7960 r9987  
    3333   USE step_oce         ! time stepping definition modules 
    3434   USE iom 
     35   USE lbclnk 
    3536 
    3637   IMPLICIT NONE 
     
    5051 
    5152#if defined key_agrif 
    52    SUBROUTINE stp( ) 
     53   RECURSIVE SUBROUTINE stp( ) 
    5354      INTEGER             ::   kstp   ! ocean time-step index 
    5455#else 
     
    7374      !!---------------------------------------------------------------------- 
    7475      INTEGER ::   jk       ! dummy loop indice 
     76      INTEGER ::   tind     ! tracer loop index 
    7577      INTEGER ::   indic    ! error indicator if < 0 
    7678      INTEGER ::   kcall    ! optional integer argument (dom_vvl_sf_nxt) 
     
    7981#if defined key_agrif 
    8082      kstp = nit000 + Agrif_Nb_Step() 
    81 !      IF ( Agrif_Root() .and. lwp) Write(*,*) '---' 
    82 !      IF (lwp) Write(*,*) 'Grid Number',Agrif_Fixed(),' time step ',kstp 
     83      IF ( lk_agrif_debug ) THEN 
     84         IF ( Agrif_Root() .and. lwp) Write(*,*) '---' 
     85         IF (lwp) Write(*,*) 'Grid Number',Agrif_Fixed(),' time step ',kstp, 'int tstep',Agrif_NbStepint() 
     86      ENDIF 
     87 
    8388      IF ( kstp == (nit000 + 1) ) lk_agrif_fstep = .FALSE. 
     89 
    8490# if defined key_iomput 
    8591      IF( Agrif_Nbstepint() == 0 )   CALL iom_swap( cxios_context ) 
     
    97103      IF( ln_crs     )       CALL iom_setkt( kstp - nit000 + 1, TRIM(cxios_context)//"_crs" )   ! tell iom we are at time step kstp 
    98104 
     105      IF( ln_bias )          CALL bias_opn( kstp ) 
     106 
    99107      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    100108      ! Update data, open boundaries, surface boundary condition (including sea-ice) 
     
    105113                         CALL bdy_dta ( kstp, time_offset=+1 )   ! update dynamic & tracer data at open boundaries 
    106114      ENDIF 
     115 
     116      ! We must ensure that tsb halos are up to date on EVERY timestep. 
     117      DO tind = 1, jpts 
     118         CALL lbc_lnk( tsb(:,:,:,tind), 'T', 1. ) 
     119      END DO 
     120 
    107121                         CALL sbc    ( kstp )         ! Sea Boundary Condition (including sea-ice) 
    108122                                                      ! clem: moved here for bdy ice purpose 
     
    110124      ! Update stochastic parameters and random T/S fluctuations 
    111125      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    112                         CALL sto_par( kstp )          ! Stochastic parameters 
     126       IF( ln_sto_eos ) CALL sto_par( kstp )          ! Stochastic parameters 
     127       IF( ln_sto_eos ) CALL sto_pts( tsn  )          ! Random T/S fluctuations 
    113128 
    114129      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    152167      ! 
    153168      IF( lk_ldfslp ) THEN                            ! slope of lateral mixing 
    154          IF(ln_sto_eos ) CALL sto_pts( tsn )          ! Random T/S fluctuations 
    155                          CALL eos( tsb, rhd, gdept_0(:,:,:) )               ! before in situ density 
     169         CALL eos( tsb, rhd, gdept_0(:,:,:) )               ! before in situ density 
    156170         IF( ln_zps .AND. .NOT. ln_isfcav)                               & 
    157171            &            CALL zps_hde    ( kstp, jpts, tsb, gtsu, gtsv,  &  ! Partial steps: before horizontal gradient 
     
    188202          ! Note that the computation of vertical velocity above, hence "after" sea level 
    189203          ! is necessary to compute momentum advection for the rhs of barotropic loop: 
    190             IF(ln_sto_eos ) CALL sto_pts( tsn )                             ! Random T/S fluctuations 
    191                             CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) ) ! now in situ density for hpg computation 
     204            CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) ) ! now in situ density for hpg computation 
    192205            IF( ln_zps .AND. .NOT. ln_isfcav)                               & 
    193206               &            CALL zps_hde    ( kstp, jpts, tsn, gtsu, gtsv,  &    ! Partial steps: before horizontal gradient 
     
    200213                                  ua(:,:,:) = 0.e0             ! set dynamics trends to zero 
    201214                                  va(:,:,:) = 0.e0 
    202           IF(  ln_asmiau .AND. & 
     215          IF(  lk_asminc .AND. ln_asmiau .AND. & 
    203216             & ln_dyninc       )  CALL dyn_asm_inc  ( kstp )   ! apply dynamics assimilation increment 
    204217          IF( ln_neptsimp )       CALL dyn_nept_cor ( kstp )   ! subtract Neptune velocities (simplified) 
     
    231244      IF( lk_diaar5  )      CALL dia_ar5( kstp )         ! ar5 diag 
    232245      IF( lk_diaharm )      CALL dia_harm( kstp )        ! Tidal harmonic analysis 
     246                            CALL dia_prod( kstp )        ! ocean model: product diagnostics 
    233247                            CALL dia_wri( kstp )         ! ocean model: outputs 
    234248      ! 
     
    248262                             tsa(:,:,:,:) = 0.e0            ! set tracer trends to zero 
    249263 
    250       IF(  ln_asmiau .AND. & 
     264      IF(  lk_asminc .AND. ln_asmiau .AND. & 
    251265         & ln_trainc     )   CALL tra_asm_inc( kstp )       ! apply tracer assimilation increment 
    252266                             CALL tra_sbc    ( kstp )       ! surface boundary condition 
     
    255269      IF( lk_trabbl      )   CALL tra_bbl    ( kstp )       ! advective (and/or diffusive) bottom boundary layer scheme 
    256270      IF( ln_tradmp      )   CALL tra_dmp    ( kstp )       ! internal damping trends 
     271      IF( ln_bias        )   CALL tra_bias   ( kstp ) 
    257272      IF( lk_bdy         )   CALL bdy_tra_dmp( kstp )       ! bdy damping trends 
    258273                             CALL tra_adv    ( kstp )       ! horizontal & vertical advection 
     
    270285         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
    271286                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
    272             IF( ln_sto_eos ) CALL sto_pts( tsn )                 ! Random T/S fluctuations 
    273287                             CALL eos    ( tsa, rhd, rhop, fsdept_n(:,:,:) )  ! Time-filtered in situ density for hpg computation 
    274288            IF( ln_zps .AND. .NOT. ln_isfcav)                                & 
     
    279293               &                                           rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   & 
    280294               &                                    gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi    ) ! of t, s, rd at the last ocean level 
     295            IF( ln_bias )    CALL dyn_bias( kstp ) 
    281296      ELSE                                                  ! centered hpg  (eos then time stepping) 
    282297         IF ( .NOT. lk_dynspg_ts ) THEN                     ! eos already called in time-split case 
    283             IF( ln_sto_eos ) CALL sto_pts( tsn )    ! Random T/S fluctuations 
    284298                             CALL eos    ( tsn, rhd, rhop, fsdept_n(:,:,:) )  ! now in situ density for hpg computation 
    285299         IF( ln_zps .AND. .NOT. ln_isfcav)                                   & 
     
    293307         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
    294308                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
     309         IF( ln_bias )       CALL dyn_bias( kstp ) 
    295310      ENDIF 
    296311 
     
    314329                               va(:,:,:) = 0.e0 
    315330 
    316         IF(  ln_asmiau .AND. & 
     331        IF(  lk_asminc .AND. ln_asmiau .AND. & 
    317332           & ln_dyninc      )  CALL dyn_asm_inc( kstp )     ! apply dynamics assimilation increment 
    318333        IF( ln_bkgwri )        CALL asm_bkg_wri( kstp )     ! output background fields 
     
    335350                               CALL ssh_swp( kstp )         ! swap of sea surface height 
    336351      IF( lk_vvl           )   CALL dom_vvl_sf_swp( kstp )  ! swap of vertical scale factors 
    337  
     352      ! 
     353      IF( lrst_oce         )   CALL rst_write( kstp )       ! write output ocean restart file 
     354      IF( ln_sto_eos       )   CALL sto_rst_write( kstp )   ! write restart file for stochastic parameters 
     355 
     356#if defined key_agrif 
     357      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     358      ! AGRIF 
     359      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<       
     360                               CALL Agrif_Integrate_ChildGrids( stp )   
     361 
     362      IF ( Agrif_NbStepint().EQ.0 ) THEN 
     363                               CALL Agrif_Update_Tra()      ! Update active tracers 
     364                               CALL Agrif_Update_Dyn()      ! Update momentum 
     365      ENDIF 
     366#endif 
    338367      IF( ln_diahsb        )   CALL dia_hsb( kstp )         ! - ML - global conservation diagnostics 
    339368      IF( lk_diaobs  )         CALL dia_obs( kstp )         ! obs-minus-model (assimilation) diagnostics (call after dynamics update) 
    340369 
    341370      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    342       ! Control and restarts 
     371      ! Control 
    343372      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    344373                               CALL stp_ctl( kstp, indic ) 
     
    352381         IF( lwm.AND.numoni /= -1 ) CALL FLUSH    ( numoni )     ! flush output namelist ice 
    353382      ENDIF 
    354       IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file 
     383 
     384 
     385      IF( lrst_bias )          CALL bias_wrt     ( kstp ) 
    355386 
    356387      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    357388      ! Coupled mode 
    358389      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    359       IF( lk_oasis         )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
     390      !IF( lk_oasis         )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    360391      ! 
    361392#if defined key_iomput 
     
    367398      ! 
    368399      IF( nn_timing == 1 .AND.  kstp == nit000  )   CALL timing_reset 
     400      !      
    369401      ! 
    370402   END SUBROUTINE stp 
Note: See TracChangeset for help on using the changeset viewer.