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/TRP/trdmxl_trc.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/TRP/trdmxl_trc.F90

    r11536 r11949  
    1616   !!   trd_mxl_trc_init : initialization step 
    1717   !!---------------------------------------------------------------------- 
    18    USE trc               ! tracer definitions (trn, trb, tra, etc.) 
    19    USE trc_oce, ONLY :   nn_dttrc  ! frequency of step on passive tracers 
     18   USE trc               ! tracer definitions (tr etc.) 
    2019   USE dom_oce           ! domain definition 
    2120   USE zdfmxl  , ONLY : nmln ! number of level in the mixed layer 
     
    7069 
    7170 
    72    SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn ) 
     71   SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn, Kmm ) 
    7372      !!---------------------------------------------------------------------- 
    7473      !!                  ***  ROUTINE trd_mxl_trc_zint  *** 
     
    9291      !! 
    9392      INTEGER, INTENT( in ) ::   ktrd, kjn                        ! ocean trend index and passive tracer rank 
     93      INTEGER, INTENT( in ) ::   Kmm                              ! time level index 
    9494      CHARACTER(len=2), INTENT( in ) ::  ctype                    ! surface/bottom (2D) or interior (3D) physics 
    9595      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT( in ) ::  ptrc_trdmxl ! passive tracer trend 
     
    150150            DO jj = 1, jpj 
    151151               DO ji = 1, jpi 
    152                   IF( jk - nmld_trc(ji,jj) < 0 )   wkx_trc(ji,jj,jk) = e3t_n(ji,jj,jk) * tmask(ji,jj,jk) 
     152                  IF( jk - nmld_trc(ji,jj) < 0 )   wkx_trc(ji,jj,jk) = e3t(ji,jj,jk,Kmm) * tmask(ji,jj,jk) 
    153153               END DO 
    154154            END DO 
     
    183183 
    184184 
    185    SUBROUTINE trd_mxl_trc( kt ) 
     185   SUBROUTINE trd_mxl_trc( kt, Kmm ) 
    186186      !!---------------------------------------------------------------------- 
    187187      !!                  ***  ROUTINE trd_mxl_trc  *** 
     
    232232      ! 
    233233      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     234      INTEGER, INTENT(in) ::   Kmm                              ! time level index 
    234235      ! 
    235236      INTEGER ::   ji, jj, jk, jl, ik, it, itmod, jn 
     
    251252 
    252253 
    253       IF( nn_dttrc  /= 1  )   CALL ctl_stop( " Be careful, trends diags never validated " ) 
    254  
    255254      ! ====================================================================== 
    256255      ! I. Diagnose the purely vertical (K_z) diffusion trend 
     
    267266                  ik = nmld_trc(ji,jj) 
    268267                  IF( ln_trdtrc(jn) )    & 
    269                   tmltrd_trc(ji,jj,jpmxl_trc_zdf,jn) = - avs(ji,jj,ik) / e3w_n(ji,jj,ik) * tmask(ji,jj,ik)  & 
    270                        &                    * ( trn(ji,jj,ik-1,jn) - trn(ji,jj,ik,jn) )            & 
     268                  tmltrd_trc(ji,jj,jpmxl_trc_zdf,jn) = - avs(ji,jj,ik) / e3w(ji,jj,ik,Kmm) * tmask(ji,jj,ik)  & 
     269                       &                    * ( tr(ji,jj,ik-1,jn,Kmm) - tr(ji,jj,ik,jn,Kmm) )            & 
    271270                       &                    / MAX( 1., rmld_trc(ji,jj) ) * tmask(ji,jj,1) 
    272271               END DO 
     
    322321         DO jn = 1, jptra 
    323322            IF( ln_trdtrc(jn) ) & 
    324                tml_trc(:,:,jn) = tml_trc(:,:,jn) + wkx_trc(:,:,jk) * trn(:,:,jk,jn) 
     323               tml_trc(:,:,jn) = tml_trc(:,:,jn) + wkx_trc(:,:,jk) * tr(:,:,jk,jn,Kmm) 
    325324         END DO 
    326325      END DO 
     
    328327      ! II.3 Initialize mixed-layer "before" arrays for the 1rst analysis window     
    329328      ! ------------------------------------------------------------------------ 
    330       IF( kt == nittrc000 + nn_dttrc ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1)    ??? 
     329      IF( kt == nittrc000 + 1 ) THEN  !  i.e. ( .NOT. ln_rstart ).AND.( kt == nit000 + 1)    ??? 
    331330         ! 
    332331         DO jn = 1, jptra 
     
    870869#  endif 
    871870      zout = nn_trd_trc * rdt 
    872       iiter = ( nittrc000 - 1 ) / nn_dttrc 
     871      iiter = nittrc000 - 1 
    873872 
    874873      IF(lwp) WRITE (numout,*) '                netCDF initialization' 
     
    970969   !!---------------------------------------------------------------------- 
    971970CONTAINS 
    972    SUBROUTINE trd_mxl_trc( kt )                                   ! Empty routine 
     971   SUBROUTINE trd_mxl_trc( kt, Kmm )                                   ! Empty routine 
    973972      INTEGER, INTENT( in) ::   kt 
     973      INTEGER, INTENT( in) ::   Kmm            ! time level index 
    974974      WRITE(*,*) 'trd_mxl_trc: You should not have seen this print! error?', kt 
    975975   END SUBROUTINE trd_mxl_trc 
    976    SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn ) 
     976   SUBROUTINE trd_mxl_trc_zint( ptrc_trdmxl, ktrd, ctype, kjn, Kmm ) 
    977977      INTEGER               , INTENT( in ) ::  ktrd, kjn              ! ocean trend index and passive tracer rank 
     978      INTEGER               , INTENT( in ) ::  Kmm                    ! time level index 
    978979      CHARACTER(len=2)      , INTENT( in ) ::  ctype                  ! surface/bottom (2D) or interior (3D) physics 
    979980      REAL, DIMENSION(:,:,:), INTENT( in ) ::  ptrc_trdmxl            ! passive trc trend 
Note: See TracChangeset for help on using the changeset viewer.