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

Ignore:
Timestamp:
2019-09-10T17:46:18+02:00 (5 years ago)
Author:
acc
Message:

Branch 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. Removal of TOP-specific time indices (Nnn_trc etc.). This completes the removal of the trc sub-timestepping option and dynamics, active tracers and passive tracers must now have common time-steps. Note time-filtering for passive tracers is done in trc_trp (trc_atf) but the (now shared) time indices are not swapped until after calls to tra_atf, dyn_atf and ssh_atf in step. Calls to trc routines after trc_atf have had their time-index arguments adjusted accordingly. These changes have been fully SETTE-tested.

File:
1 edited

Legend:

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

    r11506 r11527  
    3838 
    3939   !!---------------------------------------------------------------------- 
    40    !! time level indices 
    41    !!---------------------------------------------------------------------- 
    42    INTEGER, PUBLIC :: Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc      !! used by trc_init 
    43  
    44    !!---------------------------------------------------------------------- 
    4540   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
    4641   !! $Id$  
     
    4944CONTAINS 
    5045 
    51    SUBROUTINE trc_stp( kt, Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ) 
     46   SUBROUTINE trc_stp( kt, Kbb, Kmm, Krhs, Kaa ) 
    5247      !!------------------------------------------------------------------- 
    5348      !!                     ***  ROUTINE trc_stp  *** 
     
    5954      !!------------------------------------------------------------------- 
    6055      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
    61       INTEGER, INTENT( in ) :: Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ! time level indices 
     56      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices 
    6257      ! 
    6358      INTEGER ::   jk, jn   ! dummy loop indices 
     
    8176      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution 
    8277         DO jk = 1, jpk 
    83             cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm_oce) * tmask(:,:,jk) 
     78            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    8479         END DO 
    8580         IF ( ln_ctl .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )              & 
     
    9186      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    9287      !     
    93       IF( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN 
    94          ! The OCE and TRC time indices should be the same always.  
    95          ! If this is not the case then something has gone wrong. 
    96          CALL ctl_stop( 'trc_stp : OCE and TRC time indices are different! Something has gone wrong.' ) 
    97       ENDIF 
    98       !     
    9988      ! 
    10089      IF(ln_ctl) THEN 
     
    10392      ENDIF 
    10493      ! 
    105       tr(:,:,:,:,Nrhs_trc) = 0.e0 
    106       ! 
    107       CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
    108       IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
    109       CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager 
    110       CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources 
    111       CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers 
     94      tr(:,:,:,:,Krhs) = 0._wp 
     95      ! 
     96      CALL trc_rst_opn  ( kt )                            ! Open tracer restart file  
     97      IF( lrst_trc )  CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
     98      CALL trc_wri      ( kt,      Kmm            )       ! output of passive tracers with iom I/O manager 
     99      CALL trc_sms      ( kt, Kbb, Kmm, Krhs      )       ! tracers: sinks and sources 
     100      CALL trc_trp      ( kt, Kbb, Kmm, Krhs, Kaa )       ! transport of passive tracers 
     101           ! 
     102           ! Note passive tracers have been time-filtered in trc_trp but the time level 
     103           ! indices will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp. Subsequent calls here 
     104           ! anticipate this update which will be: Nrhs= Nbb ; Nbb = Nnn ; Nnn = Naa ; Naa = Nrhs 
     105           ! and use the filtered levels explicitly. 
     106           ! 
    112107      IF( kt == nittrc000 ) THEN 
    113          CALL iom_close( numrtr )       ! close input tracer restart file 
    114          IF(lwm) CALL FLUSH( numont )   ! flush namelist output 
    115       ENDIF 
    116       IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file 
    117       IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer 
     108         CALL iom_close( numrtr )                         ! close input tracer restart file 
     109         IF(lwm) CALL FLUSH( numont )                     ! flush namelist output 
     110      ENDIF 
     111      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kmm, Kaa, Kbb )       ! write tracer restart file 
     112      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,      Kaa       )       ! trends: Mixed-layer 
    118113      ! 
    119114      IF (ll_trcstat) THEN 
    120115         ztrai = 0._wp                                                   !  content of all tracers 
    121116         DO jn = 1, jptra 
    122             ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Nnn_trc) * cvol(:,:,:)   ) 
     117            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   ) 
    123118         END DO 
    124119         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot 
Note: See TracChangeset for help on using the changeset viewer.