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.
trcldf.F90 in NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/TOP/TRP – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/TOP/TRP/trcldf.F90 @ 12808

Last change on this file since 12808 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 10.6 KB
Line 
1MODULE trcldf
2   !!======================================================================
3   !!                       ***  MODULE  trcldf  ***
4   !! Ocean Passive tracers : lateral diffusive trends
5   !!=====================================================================
6   !! History :  1.0  ! 2005-11  (G. Madec)  Original code
7   !!            3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            3.7  ! 2014-03  (G. Madec)  LDF simplification
9   !!----------------------------------------------------------------------
10#if defined key_top
11   !!----------------------------------------------------------------------
12   !!   'key_top'                                                TOP models
13   !!----------------------------------------------------------------------
14   !!   trc_ldf       : update the tracer trend with the lateral diffusion
15   !!   trc_ldf_ini   : initialization, namelist read, and parameters control
16   !!----------------------------------------------------------------------
17   USE trc            ! ocean passive tracers variables
18   USE oce_trc        ! ocean dynamics and active tracers
19   USE ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff.
20   USE ldfslp         ! Lateral diffusion: slopes of neutral surfaces
21   USE traldf_lap_blp ! lateral diffusion: lap/bilaplacian iso-level      operator  (tra_ldf_lap/_blp   routine)
22   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine)
23   USE traldf_triad   ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_     triad routine)
24   USE trd_oce        ! trends: ocean variables
25   USE trdtra         ! trends manager: tracers
26   !
27   USE prtctl_trc     ! Print control
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   trc_ldf   
33   PUBLIC   trc_ldf_ini   
34   !
35   !                                      !!: ** lateral mixing namelist (nam_trcldf) **
36   LOGICAL , PUBLIC ::   ln_trcldf_OFF     !: No operator (no explicit lateral diffusion)
37   LOGICAL , PUBLIC ::   ln_trcldf_tra     !: use active tracer operator
38   REAL(wp), PUBLIC ::      rn_ldf_multi      !: multiplier of T-S eddy diffusivity to obtain the passive tracer one
39   REAL(wp), PUBLIC ::      rn_fact_lap       !: enhanced Equatorial zonal diffusivity coefficent
40   !
41   INTEGER  ::   nldf_trc = 0   ! type of lateral diffusion used defined from ln_traldf_... (namlist logicals)
42   REAL(wp) ::   rldf           ! multiplier between active and passive tracers eddy diffusivity   [-]
43   
44   !! * Substitutions
45#  include "do_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
48   !! $Id$
49   !! Software governed by the CeCILL license (see ./LICENSE)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE trc_ldf( kt, Kbb, Kmm, ptr, Krhs )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_ldf  ***
56      !!
57      !! ** Purpose :   compute the lateral ocean tracer physics.
58      !!
59      !!----------------------------------------------------------------------
60      INTEGER,                                    INTENT(in   ) :: kt              ! ocean time-step index
61      INTEGER,                                    INTENT(in   ) :: Kbb, Kmm, Krhs  ! ocean time-level index
62      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra,jpt), INTENT(inout) :: ptr             ! passive tracers and RHS of tracer equation
63      !
64      INTEGER            :: ji, jj, jk, jn
65      REAL(wp)           :: zdep
66      CHARACTER (len=22) :: charout
67      REAL(wp),          DIMENSION(jpi,jpj,jpk) ::   zahu, zahv
68      REAL(wp), POINTER, DIMENSION(:,:,:,:)     ::   ztrtrd
69      !!----------------------------------------------------------------------
70      !
71      IF( ln_trcldf_OFF )   RETURN        ! not lateral diffusion applied on passive tracers
72      !
73      IF( ln_timing )   CALL timing_start('trc_ldf')
74      !
75      IF( l_trdtrc )  THEN
76         ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) )
77         ztrtrd(:,:,:,:)  = ptr(:,:,:,:,Krhs)
78      ENDIF
79      !                                  !* set the lateral diffusivity coef. for passive tracer     
80      zahu(:,:,:) = rldf * ahtu(:,:,:) 
81      zahv(:,:,:) = rldf * ahtv(:,:,:)
82      !                                  !* Enhanced zonal diffusivity coefficent in the equatorial domain
83      DO_3D_11_11( 1, jpk )
84         IF( gdept(ji,jj,jk,Kmm) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN
85            zdep = MAX( gdept(ji,jj,jk,Kmm) - 1000., 0. ) / 1000.
86            zahu(ji,jj,jk) = zahu(ji,jj,jk) * MAX( 1., rn_fact_lap * EXP( -zdep ) )
87         ENDIF
88      END_3D
89      !
90      SELECT CASE ( nldf_trc )                 !* compute lateral mixing trend and add it to the general trend
91      !
92      CASE ( np_lap   )                                                                                    ! iso-level laplacian
93         CALL tra_ldf_lap  ( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            &
94           &                     ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs),                   jptra, 1 )
95      CASE ( np_lap_i )                                                                                    ! laplacian : standard iso-neutral operator (Madec)
96         CALL tra_ldf_iso  ( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            &
97           &                     ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, 1 )
98      CASE ( np_lap_it )                                                                                   ! laplacian : triad iso-neutral operator (griffies)
99         CALL tra_ldf_triad( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            &
100           &                     ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Kbb), ptr(:,:,:,:,Krhs), jptra, 1 )
101      CASE ( np_blp , np_blp_i , np_blp_it )                                                               ! bilaplacian: all operator (iso-level, -neutral)
102         CALL tra_ldf_blp  ( kt, Kmm, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi,            &
103           &                     ptr(:,:,:,:,Kbb) , ptr(:,:,:,:,Krhs),                 jptra, nldf_trc )
104      END SELECT
105      !
106      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics
107        DO jn = 1, jptra
108           ztrtrd(:,:,:,jn) = ptr(:,:,:,jn,Krhs) - ztrtrd(:,:,:,jn)
109           CALL trd_tra( kt, Kmm, Krhs, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
110        END DO
111        DEALLOCATE( ztrtrd )
112      ENDIF
113      !               
114      IF( sn_cfctl%l_prttrc ) THEN ! print mean trends (used for debugging)
115         WRITE(charout, FMT="('ldf ')")
116         CALL prt_ctl_trc_info(charout)
117         CALL prt_ctl_trc( tab4d=ptr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
118      ENDIF
119      !
120      IF( ln_timing )   CALL timing_stop('trc_ldf')
121      !
122   END SUBROUTINE trc_ldf
123
124
125   SUBROUTINE trc_ldf_ini
126      !!----------------------------------------------------------------------
127      !!                  ***  ROUTINE ldf_ctl  ***
128      !!
129      !! ** Purpose :   Define the operator for the lateral diffusion
130      !!
131      !! ** Method  : - ln_trcldf_tra=T : use nldf_tra set in ldftra module
132      !!              to defined the passive tracer lateral diffusive operator
133      !!              - ln_trcldf_OFF=T : no explicit diffusion used
134      !!----------------------------------------------------------------------
135      INTEGER ::   ios, ioptio   ! local integers
136      !!
137      NAMELIST/namtrc_ldf/ ln_trcldf_OFF , ln_trcldf_tra,   &   ! operator & direction
138         &                 rn_ldf_multi  , rn_fact_lap          ! coefficient
139      !!----------------------------------------------------------------------
140      !
141      IF(lwp) THEN
142         WRITE(numout,*)
143         WRITE(numout,*) 'trc_ldf_ini : lateral passive tracer diffusive operator'
144         WRITE(numout,*) '~~~~~~~~~~~'
145      ENDIF
146      !
147      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
148903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist' )
149      !
150      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
151904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist' )
152      IF(lwm) WRITE ( numont, namtrc_ldf )
153      !
154      IF(lwp) THEN                     ! Namelist print
155         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
156         WRITE(numout,*) '      no explicit diffusion                 ln_trcldf_OFF   = ', ln_trcldf_OFF
157         WRITE(numout,*) '      use active tracer operator            ln_trcldf_tra   = ', ln_trcldf_tra
158         WRITE(numout,*) '      diffusivity coefficient :'
159         WRITE(numout,*) '         multiplier of TRA coef. for TRC       rn_ldf_multi = ', rn_ldf_multi
160         WRITE(numout,*) '         enhanced zonal Eq. laplacian coef.    rn_fact_lap  = ', rn_fact_lap
161
162      ENDIF
163      !     
164      !                                ! control the namelist parameters
165      nldf_trc = np_ERROR
166      ioptio   = 0
167      IF( ln_trcldf_OFF  ) THEN   ;   nldf_trc = np_no_ldf   ;   ioptio = ioptio + 1   ;   ENDIF
168      IF( ln_trcldf_tra  ) THEN   ;   nldf_trc = nldf_tra    ;   ioptio = ioptio + 1   ;   ENDIF
169      IF( ioptio /=  1   )   CALL ctl_stop( 'trc_ldf_ini: use ONE of the 2 operator options (OFF/tra)' )
170     
171      !                                ! multiplier : passive/active tracers ration
172      IF( ln_traldf_lap ) THEN               ! laplacian operator
173         rldf = rn_ldf_multi                       ! simple multiplier
174      ELSEIF( ln_traldf_blp ) THEN           ! bilaplacian operator:
175         rldf = SQRT( ABS( rn_ldf_multi )  )       ! the coef. used is the SQRT of the bilaplacian coef.
176      ENDIF
177      !
178      IF(lwp) THEN
179         WRITE(numout,*)
180         SELECT CASE( nldf_trc )
181         CASE( np_no_ldf )   ;   WRITE(numout,*) '      ===>>   NO lateral diffusion'
182         CASE( np_lap    )   ;   WRITE(numout,*) '      ===>>   laplacian iso-level operator'
183         CASE( np_lap_i  )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (standard)'
184         CASE( np_lap_it )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (triad)'
185         CASE( np_blp    )   ;   WRITE(numout,*) '      ===>>   bilaplacian iso-level operator'
186         CASE( np_blp_i  )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (standard)'
187         CASE( np_blp_it )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (triad)'
188         END SELECT
189      ENDIF
190      !
191   END SUBROUTINE trc_ldf_ini
192
193#endif
194   !!======================================================================
195END MODULE trcldf
Note: See TracBrowser for help on using the repository browser.