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 branches/2016/dev_r6519_HPC_4/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2016/dev_r6519_HPC_4/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 @ 7037

Last change on this file since 7037 was 7037, checked in by mocavero, 8 years ago

ORCA2_LIM_PISCES hybrid version update

  • Property svn:keywords set to Id
File size: 15.9 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 ldfslp         ! lateral diffusion: iso-neutral slope
20   USE traldf_lap_blp ! lateral diffusion: lap/bilaplacian iso-level      operator  (tra_ldf_lap/_blp   routine)
21   USE traldf_iso     ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso        routine)
22   USE traldf_triad   ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_     triad routine)
23   USE trd_oce        ! trends: ocean variables
24   USE trdtra         ! trends manager: tracers
25   !
26   USE prtctl_trc     ! Print control
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   trc_ldf   
32   PUBLIC   trc_ldf_ini   
33   !
34   LOGICAL , PUBLIC ::   ln_trcldf_lap       !:   laplacian operator
35   LOGICAL , PUBLIC ::   ln_trcldf_blp       !: bilaplacian operator
36   LOGICAL , PUBLIC ::   ln_trcldf_lev       !: iso-level   direction
37   LOGICAL , PUBLIC ::   ln_trcldf_hor       !: horizontal  direction (rotation to geopotential)
38   LOGICAL , PUBLIC ::   ln_trcldf_iso       !: iso-neutral direction (standard)
39   LOGICAL , PUBLIC ::   ln_trcldf_triad     !: iso-neutral direction (triad)
40   REAL(wp), PUBLIC ::   rn_ahtrc_0          !:   laplacian diffusivity coefficient for passive tracer [m2/s]
41   REAL(wp), PUBLIC ::   rn_bhtrc_0          !: bilaplacian      -          --     -       -   [m4/s]
42   REAL(wp), PUBLIC ::   rn_fact_lap         !: Enhanced zonal diffusivity coefficent in the equatorial domain
43   !
44   !                      !!: ** lateral mixing namelist (nam_trcldf) **
45   REAL(wp) ::  rldf       ! ratio between active and passive tracers diffusive coefficient
46   
47   INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals)
48   
49   !! * Substitutions
50#  include "vectopt_loop_substitute.h90"
51   !!----------------------------------------------------------------------
52   !! NEMO/TOP 3.7 , NEMO Consortium (2014)
53   !! $Id$
54   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56CONTAINS
57
58   SUBROUTINE trc_ldf( kt )
59      !!----------------------------------------------------------------------
60      !!                  ***  ROUTINE tra_ldf  ***
61      !!
62      !! ** Purpose :   compute the lateral ocean tracer physics.
63      !!
64      !!----------------------------------------------------------------------
65      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
66      !
67      INTEGER            :: ji, jj, jk, jn
68      REAL(wp)           :: zdep
69      CHARACTER (len=22) :: charout
70      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zahu, zahv
71      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd
72      !!----------------------------------------------------------------------
73      !
74      IF( nn_timing == 1 )   CALL timing_start('trc_ldf')
75      !
76      IF( l_trdtrc )  THEN
77         CALL wrk_alloc( jpi,jpj,jpk,jptra,   ztrtrd )
78!$OMP PARALLEL WORKSHARE
79         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
80!$OMP END PARALLEL WORKSHARE
81      ENDIF
82      !                                  !* set the lateral diffusivity coef. for passive tracer     
83      CALL wrk_alloc( jpi,jpj,jpk,   zahu, zahv )
84!$OMP PARALLEL
85!$OMP WORKSHARE
86      zahu(:,:,:) = rldf * ahtu(:,:,:) 
87      zahv(:,:,:) = rldf * ahtv(:,:,:)
88!$OMP END WORKSHARE
89      !                                  !* Enhanced zonal diffusivity coefficent in the equatorial domain
90!$OMP DO schedule(static) private(jk,jj,ji,zdep)
91      DO jk= 1, jpk
92         DO jj = 1, jpj
93            DO ji = 1, jpi
94               IF( gdept_n(ji,jj,jk) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN
95                  zdep = MAX( gdept_n(ji,jj,jk) - 1000., 0. ) / 1000.
96                  zahu(ji,jj,jk) = zahu(ji,jj,jk) * MAX( 1., rn_fact_lap * EXP( -zdep ) )
97               ENDIF
98            END DO
99         END DO
100      END DO
101!$OMP END DO NOWAIT
102!$OMP END PARALLEL
103      !
104      SELECT CASE ( nldf )                     !* compute lateral mixing trend and add it to the general trend
105      !
106      CASE ( np_lap   )                               ! iso-level laplacian
107         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,  1   )
108         !
109      CASE ( np_lap_i )                               ! laplacian : standard iso-neutral operator (Madec)
110         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   )
111         !
112      CASE ( np_lap_it )                              ! laplacian : triad iso-neutral operator (griffies)
113         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   )
114         !
115      CASE ( np_blp , np_blp_i , np_blp_it )          ! bilaplacian: all operator (iso-level, -neutral)
116         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf )
117         !
118      END SELECT
119      !
120      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics
121        DO jn = 1, jptra
122!$OMP PARALLEL WORKSHARE
123           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn)
124!$OMP END PARALLEL WORKSHARE
125           CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
126        END DO
127        CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd )
128      ENDIF
129      !               
130      IF( ln_ctl ) THEN                        ! print mean trends (used for debugging)
131         WRITE(charout, FMT="('ldf ')")
132         CALL prt_ctl_trc_info(charout)
133         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
134      ENDIF
135      !
136      CALL wrk_dealloc( jpi,jpj,jpk,   zahu, zahv )
137      !
138      IF( nn_timing == 1 )   CALL timing_stop('trc_ldf')
139      !
140   END SUBROUTINE trc_ldf
141
142
143   SUBROUTINE trc_ldf_ini
144      !!----------------------------------------------------------------------
145      !!                  ***  ROUTINE ldf_ctl  ***
146      !!
147      !! ** Purpose :   Define the operator for the lateral diffusion
148      !!
149      !! ** Method  :   set nldf from the namtra_ldf logicals
150      !!      nldf ==  0   laplacian operator
151      !!      nldf ==  1   Rotated laplacian operator
152      !!      nldf ==  2   bilaplacian operator
153      !!      nldf ==  3   Rotated bilaplacian
154      !!----------------------------------------------------------------------
155      INTEGER ::   ioptio, ierr   ! temporary integers
156      INTEGER ::   ios            ! Local integer output status for namelist read
157      !!
158      NAMELIST/namtrc_ldf/ ln_trcldf_lap, ln_trcldf_blp,                                  &
159         &                 ln_trcldf_lev, ln_trcldf_hor, ln_trcldf_iso, ln_trcldf_triad,  &
160         &                 rn_ahtrc_0   , rn_bhtrc_0, rn_fact_lap 
161      !!----------------------------------------------------------------------
162      !
163      REWIND( numnat_ref )             !  namtrc_ldf in reference namelist
164      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
165903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
166      !
167      REWIND( numnat_cfg )             !  namtrc_ldf in configuration namelist
168      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
169904   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
170      IF(lwm) WRITE ( numont, namtrc_ldf )
171      !
172      IF(lwp) THEN                     ! Namelist print
173         WRITE(numout,*)
174         WRITE(numout,*) 'trc_ldf_ini : lateral tracer diffusive operator'
175         WRITE(numout,*) '~~~~~~~~~~~'
176         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
177         WRITE(numout,*) '      operator'
178         WRITE(numout,*) '           laplacian                 ln_trcldf_lap   = ', ln_trcldf_lap
179         WRITE(numout,*) '         bilaplacian                 ln_trcldf_blp   = ', ln_trcldf_blp
180         WRITE(numout,*) '      direction of action'
181         WRITE(numout,*) '         iso-level                   ln_trcldf_lev   = ', ln_trcldf_lev
182         WRITE(numout,*) '         horizontal (geopotential)   ln_trcldf_hor   = ', ln_trcldf_hor
183         WRITE(numout,*) '         iso-neutral (standard)      ln_trcldf_iso   = ', ln_trcldf_iso
184         WRITE(numout,*) '         iso-neutral (triad)         ln_trcldf_triad = ', ln_trcldf_triad
185         WRITE(numout,*) '      diffusivity coefficient'
186         WRITE(numout,*) '           laplacian                 rn_ahtrc_0      = ', rn_ahtrc_0
187         WRITE(numout,*) '         bilaplacian                 rn_bhtrc_0      = ', rn_bhtrc_0
188         WRITE(numout,*) '      enhanced zonal diffusivity     rn_fact_lap     = ', rn_fact_lap
189
190      ENDIF
191      !     
192      !                                ! control the namelist parameters
193      ioptio = 0
194      IF( ln_trcldf_lap )   ioptio = ioptio + 1
195      IF( ln_trcldf_blp )   ioptio = ioptio + 1
196      IF( ioptio >  1   )   CALL ctl_stop( 'trc_ldf_ctl: use ONE or NONE of the 2 lap/bilap operator type on tracer' )
197      IF( ioptio == 0   )   nldf = np_no_ldf   ! No lateral diffusion
198     
199      IF( ln_trcldf_lap .AND. ln_trcldf_blp )   CALL ctl_stop( 'trc_ldf_ctl: bilaplacian should be used on both TRC and TRA' )
200      IF( ln_trcldf_blp .AND. ln_trcldf_lap )   CALL ctl_stop( 'trc_ldf_ctl:   laplacian should be used on both TRC and TRA' )
201      !
202      ioptio = 0
203      IF( ln_trcldf_lev )   ioptio = ioptio + 1
204      IF( ln_trcldf_hor )   ioptio = ioptio + 1
205      IF( ln_trcldf_iso )   ioptio = ioptio + 1
206      IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ctl: use only ONE direction (level/hor/iso)' )
207      !
208      ! defined the type of lateral diffusion from ln_trcldf_... logicals
209      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully
210      ierr = 0
211      IF( ln_trcldf_lap ) THEN      !==  laplacian operator  ==!
212         IF ( ln_zco ) THEN                ! z-coordinate
213            IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level = horizontal (no rotation)
214            IF ( ln_trcldf_hor   )   nldf = np_lap     ! iso-level = horizontal (no rotation)
215            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard  (   rotation)
216            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad     (   rotation)
217         ENDIF
218         IF ( ln_zps ) THEN             ! z-coordinate with partial step
219            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed
220            IF ( ln_trcldf_hor   )   nldf = np_lap     ! horizontal (no rotation)
221            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation)
222            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation)
223         ENDIF
224         IF ( ln_sco ) THEN             ! s-coordinate
225            IF ( ln_trcldf_lev   )   nldf = np_lap     ! iso-level  (no rotation)
226            IF ( ln_trcldf_hor   )   nldf = np_lap_it  ! horizontal (   rotation)       !!gm   a checker....
227            IF ( ln_trcldf_iso   )   nldf = np_lap_i   ! iso-neutral: standard (rotation)
228            IF ( ln_trcldf_triad )   nldf = np_lap_it  ! iso-neutral: triad    (rotation)
229         ENDIF
230         !                                ! diffusivity ratio: passive / active tracers
231         IF( ABS(rn_aht_0) < 2._wp*TINY(1._wp) ) THEN
232            IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1._wp) ) THEN
233               rldf = 1.0_wp
234            ELSE
235               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' )
236            ENDIF
237         ELSE
238            rldf = rn_ahtrc_0 / rn_aht_0
239         ENDIF
240      ENDIF
241      !
242      IF( ln_trcldf_blp ) THEN      !==  bilaplacian operator  ==!
243         IF ( ln_zco ) THEN                ! z-coordinate
244            IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level = horizontal (no rotation)
245            IF ( ln_trcldf_hor   )   nldf = np_blp     ! iso-level = horizontal (no rotation)
246            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation)
247            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation)
248         ENDIF
249         IF ( ln_zps ) THEN             ! z-coordinate with partial step
250            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed
251            IF ( ln_trcldf_hor   )   nldf = np_blp     ! horizontal (no rotation)
252            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation)
253            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation)
254         ENDIF
255         IF ( ln_sco ) THEN             ! s-coordinate
256            IF ( ln_trcldf_lev   )   nldf = np_blp     ! iso-level  (no rotation)
257            IF ( ln_trcldf_hor   )   nldf = np_blp_it  ! horizontal (   rotation)       !!gm   a checker....
258            IF ( ln_trcldf_iso   )   nldf = np_blp_i   ! iso-neutral: standard (rotation)
259            IF ( ln_trcldf_triad )   nldf = np_blp_it  ! iso-neutral: triad    (rotation)
260         ENDIF
261         !                                ! diffusivity ratio: passive / active tracers
262         IF( ABS(rn_bht_0) < 2._wp*TINY(1._wp) ) THEN
263            IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1._wp) ) THEN
264               rldf = 1.0_wp
265            ELSE
266               CALL ctl_stop( 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' )
267            ENDIF
268         ELSE
269            rldf = SQRT(  ABS( rn_bhtrc_0 / rn_bht_0 )  )
270         ENDIF
271      ENDIF
272      !
273      IF( ierr == 1 )   CALL ctl_stop( 'trc_ldf_ctl: iso-level in z-partial step, not allowed' )
274      IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   CALL ctl_stop( 'trc_ldf_ctl: eiv requires isopycnal laplacian diffusion' )
275      IF( nldf == 1 .OR. nldf == 3 )   l_ldfslp = .TRUE.    ! slope of neutral surfaces required
276      !
277      IF(lwp) THEN
278         WRITE(numout,*)
279         SELECT CASE( nldf )
280         CASE( np_no_ldf )   ;   WRITE(numout,*) '          NO lateral diffusion'
281         CASE( np_lap    )   ;   WRITE(numout,*) '          laplacian iso-level operator'
282         CASE( np_lap_i  )   ;   WRITE(numout,*) '          Rotated laplacian operator (standard)'
283         CASE( np_lap_it )   ;   WRITE(numout,*) '          Rotated laplacian operator (triad)'
284         CASE( np_blp    )   ;   WRITE(numout,*) '          bilaplacian iso-level operator'
285         CASE( np_blp_i  )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (standard)'
286         CASE( np_blp_it )   ;   WRITE(numout,*) '          Rotated bilaplacian operator (triad)'
287         END SELECT
288      ENDIF
289      !
290   END SUBROUTINE trc_ldf_ini
291#else
292   !!----------------------------------------------------------------------
293   !!   Default option                                         Empty module
294   !!----------------------------------------------------------------------
295CONTAINS
296   SUBROUTINE trc_ldf( kt )
297      INTEGER, INTENT(in) :: kt
298      WRITE(*,*) 'trc_ldf: You should not have seen this print! error?', kt
299   END SUBROUTINE trc_ldf
300#endif
301   !!======================================================================
302END MODULE trcldf
Note: See TracBrowser for help on using the repository browser.