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 11949 for NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/trcstp.F90 – NEMO

Ignore:
Timestamp:
2019-11-22T15:29:17+01:00 (4 years ago)
Author:
acc
Message:

Merge in changes from 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. This just creates a fresh copy of this branch to use as the merge base. See ticket #2341

Location:
NEMO/branches/2019/dev_r11943_MERGE_2019/src
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src

    • Property svn:mergeinfo deleted
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/trcstp.F90

    r10570 r11949  
    55   !!====================================================================== 
    66   !! History :  1.0  !  2004-03  (C. Ethe)  Original 
     7   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme 
    78   !!---------------------------------------------------------------------- 
    89#if defined key_top 
     
    1718   USE trcwri 
    1819   USE trcrst 
    19    USE trcsub         ! 
    2020   USE trdtrc_oce 
    2121   USE trdmxl_trc 
     
    4444CONTAINS 
    4545 
    46    SUBROUTINE trc_stp( kt ) 
     46   SUBROUTINE trc_stp( kt, Kbb, Kmm, Krhs, Kaa ) 
    4747      !!------------------------------------------------------------------- 
    4848      !!                     ***  ROUTINE trc_stp  *** 
     
    5353      !!                Update the passive tracers 
    5454      !!------------------------------------------------------------------- 
    55       INTEGER, INTENT( in ) ::   kt   ! ocean time-step index 
     55      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index 
     56      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices 
    5657      ! 
    5758      INTEGER ::   jk, jn   ! dummy loop indices 
     
    6566      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN     ! at nittrc000 
    6667         r2dttrc =  rdttrc           ! = rdttrc (use or restarting with Euler time stepping) 
    67       ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1 
    68          r2dttrc = 2. * rdttrc       ! = 2 rdttrc (leapfrog) 
     68      ELSEIF( kt <= nittrc000 + 1 ) THEN                                     ! at nittrc000 or nittrc000+1  
     69         r2dttrc = 2. * rdttrc       ! = 2 rdttrc (leapfrog)  
    6970      ENDIF 
    7071      ! 
     
    7576      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution 
    7677         DO jk = 1, jpk 
    77             cvol(:,:,jk) = e1e2t(:,:) * e3t_n(:,:,jk) * tmask(:,:,jk) 
     78            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    7879         END DO 
    7980         IF ( ln_ctl .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )              & 
     
    8586      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt ) 
    8687      !     
    87       IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt )  ! averaging physical variables for sub-stepping 
    88       !     
    89       IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step 
    90          ! 
    91          IF(ln_ctl) THEN 
    92             WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
    93             CALL prt_ctl_trc_info(charout) 
    94          ENDIF 
    95          ! 
    96          tra(:,:,:,:) = 0.e0 
    97          ! 
    98                                    CALL trc_rst_opn  ( kt )       ! Open tracer restart file  
    99          IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar 
    100                                    CALL trc_wri      ( kt )       ! output of passive tracers with iom I/O manager 
    101                                    CALL trc_sms      ( kt )       ! tracers: sinks and sources 
    102                                    CALL trc_trp      ( kt )       ! transport of passive tracers 
    103          IF( kt == nittrc000 ) THEN 
    104             CALL iom_close( numrtr )       ! close input tracer restart file 
    105             IF(lwm) CALL FLUSH( numont )   ! flush namelist output 
    106          ENDIF 
    107          IF( lrst_trc )            CALL trc_rst_wri  ( kt )       ! write tracer restart file 
    108          IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt )       ! trends: Mixed-layer 
    109          ! 
    110          IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt )       ! resetting physical variables when sub-stepping 
    111          ! 
    112       ENDIF 
     88      ! 
     89      IF(ln_ctl) THEN 
     90         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     91         CALL prt_ctl_trc_info(charout) 
     92      ENDIF 
     93      ! 
     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           ! 
     107      IF( kt == nittrc000 ) THEN 
     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 
    113113      ! 
    114114      IF (ll_trcstat) THEN 
    115115         ztrai = 0._wp                                                   !  content of all tracers 
    116116         DO jn = 1, jptra 
    117             ztrai = ztrai + glob_sum( 'trcstp', trn(:,:,:,jn) * cvol(:,:,:)   ) 
     117            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   ) 
    118118         END DO 
    119119         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot 
     
    124124      ! 
    125125   END SUBROUTINE trc_stp 
    126  
    127126 
    128127   SUBROUTINE trc_mean_qsr( kt ) 
Note: See TracChangeset for help on using the changeset viewer.