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/trcdmp.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/trcdmp.F90

    r11536 r11949  
    6363 
    6464 
    65    SUBROUTINE trc_dmp( kt ) 
     65   SUBROUTINE trc_dmp( kt, Kbb, Kmm, ptr, Krhs ) 
    6666      !!---------------------------------------------------------------------- 
    6767      !!                   ***  ROUTINE trc_dmp  *** 
     
    7373      !! ** Method  :   Newtonian damping towards trdta computed  
    7474      !!      and add to the general tracer trends: 
    75       !!                     trn = tra + restotr * (trdta - trb) 
     75      !!                     tr(Kmm) = tr(Krhs) + restotr * (trdta - tr(Kbb)) 
    7676      !!         The trend is computed either throughout the water column 
    7777      !!      (nlmdmptr=0) or in area of weak vertical mixing (nlmdmptr=1) or 
    7878      !!      below the well mixed layer (nlmdmptr=2) 
    7979      !! 
    80       !! ** Action  : - update the tracer trends tra with the newtonian  
     80      !! ** Action  : - update the tracer trends tr(:,:,:,:,Krhs) with the newtonian  
    8181      !!                damping trends. 
    8282      !!              - save the trends ('key_trdmxl_trc') 
    8383      !!---------------------------------------------------------------------- 
    84       INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
     84      INTEGER,                                    INTENT(in   ) :: kt              ! ocean time-step index 
     85      INTEGER,                                    INTENT(in   ) :: Kbb, Kmm, Krhs  ! time level indices 
     86      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation 
    8587      ! 
    8688      INTEGER ::   ji, jj, jk, jn, jl   ! dummy loop indices 
     
    100102         DO jn = 1, jptra                                           ! tracer loop 
    101103            !                                                       ! =========== 
    102             IF( l_trdtrc ) ztrtrd(:,:,:) = tra(:,:,:,jn)    ! save trends  
     104            IF( l_trdtrc ) ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs)    ! save trends  
    103105            ! 
    104106            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    105107               ! 
    106108               jl = n_trc_index(jn)  
    107                CALL trc_dta( kt, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000 
     109               CALL trc_dta( kt, Kmm, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000 
    108110               ! 
    109111               SELECT CASE ( nn_zdmp_tr ) 
     
    113115                     DO jj = 2, jpjm1 
    114116                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    115                            tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) 
     117                           ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) ) 
    116118                        END DO 
    117119                     END DO 
     
    123125                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    124126                           IF( avt(ji,jj,jk) <= avt_c )  THEN  
    125                               tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) 
     127                              ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) ) 
    126128                           ENDIF 
    127129                        END DO 
     
    133135                     DO jj = 2, jpjm1 
    134136                        DO ji = fs_2, fs_jpim1   ! vector opt. 
    135                            IF( gdept_n(ji,jj,jk) >= hmlp (ji,jj) ) THEN 
    136                               tra(ji,jj,jk,jn) = tra(ji,jj,jk,jn) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - trb(ji,jj,jk,jn) ) 
     137                           IF( gdept(ji,jj,jk,Kmm) >= hmlp (ji,jj) ) THEN 
     138                              ptr(ji,jj,jk,jn,Krhs) = ptr(ji,jj,jk,jn,Krhs) + restotr(ji,jj,jk) * ( ztrcdta(ji,jj,jk) - ptr(ji,jj,jk,jn,Kbb) ) 
    137139                           END IF 
    138140                        END DO 
     
    145147            ! 
    146148            IF( l_trdtrc ) THEN 
    147                ztrtrd(:,:,:) = tra(:,:,:,jn) -  ztrtrd(:,:,:) 
    148                CALL trd_tra( kt, 'TRC', jn, jptra_dmp, ztrtrd ) 
     149               ztrtrd(:,:,:) = ptr(:,:,:,jn,Krhs) -  ztrtrd(:,:,:) 
     150               CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_dmp, ztrtrd ) 
    149151            END IF 
    150152            !                                                       ! =========== 
     
    159161         WRITE(charout, FMT="('dmp ')") 
    160162         CALL prt_ctl_trc_info(charout) 
    161          CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
     163         CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' ) 
    162164      ENDIF 
    163165      ! 
     
    224226 
    225227 
    226    SUBROUTINE trc_dmp_clo( kt ) 
     228   SUBROUTINE trc_dmp_clo( kt, Kbb, Kmm ) 
    227229      !!--------------------------------------------------------------------- 
    228230      !!                  ***  ROUTINE trc_dmp_clo  *** 
     
    236238      !!                nctsi2(), nctsj2() : north-east Closed sea limits (i,j) 
    237239      !!---------------------------------------------------------------------- 
    238       INTEGER, INTENT( in ) ::   kt      ! ocean time-step index 
     240      INTEGER, INTENT( in ) ::   kt           ! ocean time-step index 
     241      INTEGER, INTENT( in ) ::   Kbb, Kmm     ! time level indices 
    239242      ! 
    240243      INTEGER :: ji , jj, jk, jn, jl, jc                    ! dummy loop indicesa 
     
    354357            IF( ln_trc_ini(jn) ) THEN      ! update passive tracers arrays with input data read from file 
    355358                jl = n_trc_index(jn) 
    356                 CALL trc_dta( kt, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000 
     359                CALL trc_dta( kt, Kmm, sf_trcdta(jl), rf_trfac(jl), ztrcdta )   ! read tracer data at nit000 
    357360                DO jc = 1, npncts 
    358361                   DO jk = 1, jpkm1 
    359362                      DO jj = nctsj1(jc), nctsj2(jc) 
    360363                         DO ji = nctsi1(jc), nctsi2(jc) 
    361                             trn(ji,jj,jk,jn) = ztrcdta(ji,jj,jk) 
    362                             trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn) 
     364                            tr(ji,jj,jk,jn,Kmm) = ztrcdta(ji,jj,jk) 
     365                            tr(ji,jj,jk,jn,Kbb) = tr(ji,jj,jk,jn,Kmm) 
    363366                         END DO 
    364367                      END DO 
Note: See TracChangeset for help on using the changeset viewer.