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 11480 for NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcstp.F90 – NEMO

Ignore:
Timestamp:
2019-08-29T11:23:25+02:00 (5 years ago)
Author:
davestorkey
Message:

2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps : Merge in changes from branch of branch.
Main changes:

  1. "nxt" modules renamed as "atf" and now just do Asselin time filtering. The time level swapping is achieved by swapping indices.
  2. Some additional prognostic grid variables changed to use a time dimension.

Notes:

  1. This merged branch passes SETTE tests but does not identical results to the SETTE tests with the trunk@10721 unless minor bugs to do with Euler timestepping and the OFF timestepping are fixed in the trunk (NEMO tickets #2310 and #2311).
  2. The nn_dttrc > 1 option for TOP (TOP has a different timestep to OCE) doesn't work. But it doesn't work in the trunk or NEMO 4.0 release either.
File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcstp.F90

    r11027 r11480  
    3838 
    3939   !!---------------------------------------------------------------------- 
     40   !! time level indices 
     41   !!---------------------------------------------------------------------- 
     42   INTEGER, PUBLIC :: Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc      !! used by trc_init 
     43 
     44   !!---------------------------------------------------------------------- 
    4045   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
    4146   !! $Id$  
     
    4449CONTAINS 
    4550 
    46    SUBROUTINE trc_stp( kt, Kbb, Kmm, Krhs, Kaa ) 
     51   SUBROUTINE trc_stp( kt, Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ) 
    4752      !!------------------------------------------------------------------- 
    4853      !!                     ***  ROUTINE trc_stp  *** 
     
    5459      !!------------------------------------------------------------------- 
    5560      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
    56       INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices 
     61      INTEGER, INTENT( in ) :: Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ! time level indices 
    5762      ! 
    5863      INTEGER ::   jk, jn   ! dummy loop indices 
     
    7681      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution 
    7782         DO jk = 1, jpk 
    78             cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
     83            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm_oce) * tmask(:,:,jk) 
    7984         END DO 
    8085         IF ( ln_ctl .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )              & 
     
    8691      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    8792      !     
    88       IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt, Kbb, Kmm, Krhs )  ! averaging physical variables for sub-stepping 
     93      IF( nn_dttrc == 1 )  THEN 
     94         IF(lwp) WRITE(numout,*) "Kbb_oce, Kmm_oce, Kaa_oce, Krhs_oce : ",Kbb_oce, Kmm_oce, Kaa_oce, Krhs_oce 
     95         IF(lwp) WRITE(numout,*) "Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc : ",Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc 
     96         IF(lwp) CALL FLUSH(numout) 
     97         CALL mppsync()       
     98         IF( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN 
     99            ! The nn_dttrc == 1 case depends on the OCE and TRC time indices being the same always.  
     100            ! If this is not the case then something has gone wrong. 
     101            CALL ctl_stop( 'trc_stp : nn_dttrc = 1 but OCE and TRC time indices are different! Something has gone wrong.' ) 
     102         ENDIF 
     103      ELSE 
     104         CALL trc_sub_stp( kt, Nbb_trc, Nnn_trc, Nrhs_trc )  ! averaging physical variables for sub-stepping 
     105      ENDIF 
    89106      !     
    90107      IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
     
    95112         ENDIF 
    96113         ! 
    97          tr(:,:,:,:,Krhs) = 0.e0 
     114         tr(:,:,:,:,Nrhs_trc) = 0.e0 
    98115         ! 
    99116                                   CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
    100117         IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
    101                                    CALL trc_wri      ( kt,      Kmm       )       ! output of passive tracers with iom I/O manager 
    102                                    CALL trc_sms      ( kt, Kbb, Kmm, Krhs )       ! tracers: sinks and sources 
    103                                    CALL trc_trp      ( kt, Kbb, Kmm, Krhs, Kaa )  ! transport of passive tracers 
     118                                   CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager 
     119                                   CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources 
     120                                   CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers 
    104121         IF( kt == nittrc000 ) THEN 
    105122            CALL iom_close( numrtr )       ! close input tracer restart file 
    106123            IF(lwm) CALL FLUSH( numont )   ! flush namelist output 
    107124         ENDIF 
    108          IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Krhs )       ! write tracer restart file 
    109          IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,      Kmm       )       ! trends: Mixed-layer 
    110          ! 
    111          IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt, Kbb, Kmm, Krhs )       ! resetting physical variables when sub-stepping 
     125         IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file 
     126         IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer 
     127         ! 
     128         IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! resetting physical variables when sub-stepping 
    112129         ! 
    113130      ENDIF 
     
    116133         ztrai = 0._wp                                                   !  content of all tracers 
    117134         DO jn = 1, jptra 
    118             ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Kmm) * cvol(:,:,:)   ) 
     135            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Nnn_trc) * cvol(:,:,:)   ) 
    119136         END DO 
    120137         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot 
Note: See TracChangeset for help on using the changeset viewer.