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.
trctrp_ctl.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trctrp_ctl.F90 @ 202

Last change on this file since 202 was 202, checked in by opalod, 19 years ago

CT : UPDATE142 : Check the consistency between passive tracers transport modules (in TRP directory) and those used for the active tracers

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 15.4 KB
Line 
1MODULE trctrp_ctl
2   !!==============================================================================
3   !!                       ***  MODULE  trctrp_ctl  ***
4   !! Ocean passive tracers:  transport option control
5   !!==============================================================================
6#if defined key_passivetrc
7   !!----------------------------------------------------------------------
8   !!   trc_trp_ctl  : control the different options of transport
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce_trc             ! ocean dynamics and active tracers variables
12   USE trc                 ! ocean passive tracers variables
13   USE trctrp_lec          ! passive tracers transport
14
15   IMPLICIT NONE
16   PRIVATE
17
18   !! * Accessibility
19   PUBLIC trc_trp_ctl   
20
21   !! * Module variable
22#if defined key_trcldf_eiv
23      LOGICAL, PARAMETER ::   lk_trcldf_eiv   = .TRUE.   !: eddy induced velocity flag
24#else   
25      LOGICAL, PARAMETER ::   lk_trcldf_eiv   = .FALSE.  !: eddy induced velocity flag
26#endif
27
28   !!----------------------------------------------------------------------
29   !!   OPA 9.0 , LODYC-IPSL (2003)
30   !!----------------------------------------------------------------------
31
32CONTAINS
33
34   SUBROUTINE trc_trp_ctl
35      !!---------------------------------------------------------------------
36      !!                  ***  ROUTINE trc_trp_ctl  ***
37      !!               
38      !! ** Purpose :   Control the consistency between cpp options for
39      !!      tracer transport
40      !!
41      !! History :
42      !!   9.0  !  04-0.  (C. Ethe)
43      !!----------------------------------------------------------------------
44
45      !!----------------------------------------------------------------------
46      !!  OPA 9.0, LODYC-IPSL (2003)
47      !!----------------------------------------------------------------------
48
49      !! Control of Advection scheme options
50      CALL trc_adv_ctl
51
52      !! Control of Lateral diffusion scheme options
53      CALL trc_ldf_ctl
54
55      !! Control of Vertival diffusion scheme options
56      CALL trc_zdf_ctl
57
58      !! Control of Newtonian damping  options
59      IF(lwp) THEN
60         WRITE(numout,*) ' *** Tracer damping option'
61         WRITE(numout,*)
62      ENDIF
63
64#if defined key_trcdmp
65      IF(lwp) THEN
66         WRITE(numout,*)' key_trcdmp is defined'
67         WRITE(numout,*)' Check trcdmp ROUTINE '
68         WRITE(numout,*)'  '
69      ENDIF
70      CALL trc_dmp_ctl
71#else
72      IF (lwp) WRITE(numout,*) ' No tracer damping'
73#endif
74
75
76   END SUBROUTINE trc_trp_ctl
77
78   SUBROUTINE trc_adv_ctl
79      !!---------------------------------------------------------------------
80      !!                  ***  ROUTINE trc_adv_ctl  ***
81      !!               
82      !! ** Purpose :   Control the consistency between cpp options for
83      !!      tracer advection schemes
84      !!
85      !! History :
86      !!   8.5  !  02-11  (G. Madec)  Original code
87      !!   9.0  !  04-0.  (C. Ethe)  adapted for passive tracers
88      !!----------------------------------------------------------------------
89
90      !! * Local declarations
91      INTEGER ::   ioptio
92
93
94      !!----------------------------------------------------------------------
95      !!  OPA 9.0, LODYC-IPSL (2003)
96      !!----------------------------------------------------------------------
97
98      ! Control of Advection scheme options
99      ! -----------------------------------
100      ioptio = 0
101      IF( ln_trcadv_cen2   )   ioptio = ioptio + 1
102      IF( ln_trcadv_tvd    )   ioptio = ioptio + 1
103      IF( ln_trcadv_muscl  )   ioptio = ioptio + 1
104      IF( ln_trcadv_muscl2 )   ioptio = ioptio + 1
105      IF( ln_trcadv_smolar )   ioptio = ioptio + 1
106
107      IF( lk_esopa ) THEN
108         IF(lwp) WRITE(numout,*) ' esopa control : the use of all scheme is forced'
109         ln_trcadv_cen2   = .TRUE.
110         ln_trcadv_tvd    = .TRUE.
111         ln_trcadv_muscl  = .TRUE.
112         ln_trcadv_muscl2 = .TRUE.
113         ln_trcadv_smolar = .TRUE.
114      ELSEIF( ioptio > 1 .OR. ioptio == 0 ) THEN
115         IF(lwp) WRITE(numout,cform_err)
116         IF(lwp) WRITE(numout,*) ' Choose one advection scheme in namelist nam_trcadv'
117         IF(lwp) WRITE(numout,*) '        ***                              ***********'
118         nstop = nstop + 1
119      ENDIF
120
121      IF( n_cla == 1 .AND. .NOT. ln_trcadv_cen2 ) THEN
122         IF(lwp) WRITE(numout,cform_err)
123         IF(lwp) WRITE(numout,*) '     cross-land advection only with 2nd order advection scheme'
124         nstop = nstop + 1
125      ENDIF
126
127   END SUBROUTINE trc_adv_ctl
128
129   SUBROUTINE trc_ldf_ctl
130      !!----------------------------------------------------------------------
131      !!                  ***  ROUTINE trc_ldf_ctl  ***
132      !!
133      !! ** Purpose :   Control the consistency between cpp options for
134      !!      tracer lateral diffusion
135      !!
136      !! History :
137      !!   9.0  !  03-04  (C. Ethe)
138      !!----------------------------------------------------------------------
139      !! * Local declarations
140      INTEGER ::   ioptio               ! ???
141      LOGICAL ::   ll_print = .FALSE.   ! =T print eddy coef. in numout     
142
143      !!----------------------------------------------------------------------
144      !!  OPA 9.0, LODYC-IPSL (2003)
145      !!----------------------------------------------------------------------
146
147      ! Parameter control
148
149      ! control the input
150      ioptio = 0
151      IF( ln_trcldf_lap   )   ioptio = ioptio + 1
152      IF( ln_trcldf_bilap )   ioptio = ioptio + 1
153      IF( ioptio /= 1 )   THEN
154          IF(lwp) WRITE(numout,cform_err)
155          IF(lwp) WRITE(numout,*) '          use ONE of the 2 lap/bilap operator type on tracer'
156          nstop = nstop + 1
157      ENDIF
158      ioptio = 0
159      IF( ln_trcldf_level )   ioptio = ioptio + 1
160      IF( ln_trcldf_hor   )   ioptio = ioptio + 1
161      IF( ln_trcldf_iso   )   ioptio = ioptio + 1
162      IF( ioptio /= 1 ) THEN
163         IF(lwp) WRITE(numout,cform_err)
164         IF(lwp) WRITE(numout,*) '          use only ONE direction (level/hor/iso)'
165         nstop = nstop + 1
166      ENDIF
167
168      ! ... Choice of the lateral scheme used
169      IF( lk_trcldf_eiv ) THEN
170         IF(lwp) WRITE(numout,*) '          eddy induced velocity on tracers'
171            IF( .NOT.ln_trcldf_iso .OR. ln_trcldf_bilap ) THEN
172            IF(lwp) WRITE(numout,cform_err)
173            IF(lwp) WRITE(numout,*) ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion'
174            nstop = nstop + 1
175         ENDIF
176      ENDIF
177
178      IF( lk_sco ) THEN          ! s-coordinates: rotation required for horizontal or isopycnal mixing
179         IF( ( ln_trcldf_iso .OR. ln_trcldf_hor ) .AND. .NOT.lk_ldfslp ) THEN
180            IF(lwp) WRITE(numout,cform_err)
181            IF(lwp) WRITE(numout,*) '          the rotation of the diffusive tensor require key_ldfslp'
182            IF( .NOT.lk_esopa )   nstop = nstop + 1
183         ENDIF
184      ELSE                       ! z-coordinates with/without partial step:
185         ln_trcldf_level = ln_trcldf_level .OR. ln_trcldf_hor      ! level diffusion = horizontal diffusion
186         ln_trcldf_hor   = .FALSE.
187         IF(lwp) WRITE(numout,*) '          horizontal mixing in z-coord or partial steps: force ln_trcldf_level = T'
188         IF(lwp) WRITE(numout,*) '                                                  and    force ln_trcldf_hor   = F'
189         IF( ln_trcldf_iso .AND. .NOT.lk_ldfslp ) THEN             ! rotation required for isopycnal mixing
190            IF(lwp) WRITE(numout,cform_err)
191            IF(lwp) WRITE(numout,*) '          the rotation of the diffusive tensor require key_ldfslp'
192            IF( .NOT.lk_esopa )   nstop = nstop + 1
193         ENDIF
194      ENDIF
195
196      l_trcldf_lap     =  ln_trcldf_lap   .AND. ln_trcldf_level     ! iso-level   laplacian operator
197      l_trcldf_bilap   =  ln_trcldf_bilap .AND. ln_trcldf_level     ! iso-level bilaplacian operator
198      l_trcldf_bilapg  =  ln_trcldf_bilap .AND. ln_trcldf_hor       ! geopotential bilap. (s-coord)
199      l_trcldf_iso     =  ln_trcldf_lap   .AND.                  &  ! laplacian operator
200         &                   ( ln_trcldf_iso   .OR.  ln_trcldf_hor )  &  ! iso-neutral (z-coord) or horizontal (s-coord)
201         &                                     .AND. .NOT.lk_zps
202      l_trcldf_iso_zps =       ln_trcldf_lap   .AND.                  &  ! laplacian operator
203         &                   ( ln_trcldf_iso   .OR.  ln_trcldf_hor )  &  ! iso-neutral (partial steps)
204         &                                     .AND. lk_zps              ! or geopotential in mixed partial steps/s-coord
205      l_trczdf_iso    = .FALSE.
206      l_trczdf_iso_vo = .FALSE.
207      IF( l_trcldf_iso     )   l_trczdf_iso = .TRUE.
208      IF( l_trcldf_iso_zps )   l_trczdf_iso = .TRUE.
209#if defined key_vectopt_memory
210      IF( l_trczdf_iso ) THEN
211         l_trczdf_iso    = .FALSE.
212         l_trczdf_iso_vo = .TRUE.
213      ENDIF
214#endif
215
216 
217      ioptio = 0
218      IF( l_trcldf_lap     )   ioptio = ioptio + 1
219      IF( l_trcldf_bilap   )   ioptio = ioptio + 1
220      IF( l_trcldf_bilapg  )   ioptio = ioptio + 1
221      IF( l_trcldf_iso     )   ioptio = ioptio + 1
222      IF( l_trcldf_iso_zps )   ioptio = ioptio + 1
223      IF( ioptio /= 1 ) THEN
224         IF(lwp) WRITE(numout,cform_err)
225         IF(lwp) WRITE(numout,*) '          this combination of operator and direction has not been implemented'
226         nstop = nstop + 1
227      ENDIF
228
229      IF( lk_esopa ) THEN
230         l_trcldf_lap = .TRUE.   ;   l_trcldf_bilap   = .TRUE.   ;   l_trcldf_bilapg  = .TRUE.
231         l_trcldf_iso = .TRUE.   ;   l_trcldf_iso_zps = .TRUE.
232         l_trczdf_iso = .TRUE.   ;   l_trczdf_iso_vo  = .TRUE.
233         IF(lwp ) WRITE(numout,*) '          esopa test: use all lateral physics options'
234      ENDIF
235
236      IF( .NOT. ln_trcldf_diff ) THEN
237         l_trcldf_lap = .FALSE.   ;   l_trcldf_bilap   = .FALSE.   ;   l_trcldf_bilapg  = .FALSE.
238         l_trcldf_iso = .FALSE.   ;   l_trcldf_iso_zps = .FALSE.
239         l_trczdf_iso = .FALSE.   ;   l_trczdf_iso_vo  = .FALSE.
240         IF(lwp ) WRITE(numout,*) '          No lateral physics on passive tracers'
241      ELSE
242         ! ... Space variation of eddy coefficients
243         ioptio = 0
244#if defined key_traldf_c3d
245         IF(lwp) WRITE(numout,*) 'tracer mixing coef. = F( latitude, longitude, depth)'
246         ioptio = ioptio + 1
247#endif
248#if defined key_traldf_c2d
249         IF(lwp) WRITE(numout,*) 'tracer mixing coef. = F( latitude, longitude)'
250         ioptio = ioptio + 1
251#endif
252#if defined key_traldf_c1d
253         IF(lwp) WRITE(numout,*) 'tracer mixing coef. = F( depth )'
254         ioptio = ioptio + 1
255         IF( lk_sco ) THEN
256            IF(lwp) WRITE(numout,cform_err)
257            IF(lwp) WRITE(numout,*) '          key_traldf_c1d cannot be used in s-coordinate (key_s_coord)'
258            nstop = nstop + 1
259         ENDIF
260#endif
261         IF( ioptio == 0 ) THEN
262            IF(lwp) WRITE(numout,*) ' tracer mixing coef. = constant (default option)'
263         ELSEIF( ioptio > 1 ) THEN
264            IF(lwp) WRITE(numout,cform_err)
265            IF(lwp) WRITE(numout,*) ' use only one of the following keys:',   &
266               &                    ' key_traldf_c3d, key_traldf_c2d, key_traldf_c1d'
267            nstop = nstop + 1
268         ENDIF
269         
270         IF( l_trcldf_bilap .OR. l_trcldf_bilapg ) THEN
271            IF(lwp) WRITE(numout,*) '  biharmonic tracer diffusion'
272            IF( ahtrc0 > 0 .AND. .NOT. lk_esopa ) THEN
273               IF(lwp) WRITE(numout,cform_err)
274               IF(lwp) WRITE(numout,*) ' The horizontal diffusivity coef. aht0 must be negative'
275               nstop = nstop + 1
276            ENDIF
277         ELSE
278            IF(lwp) WRITE(numout,*) ' harmonic tracer diffusion (default)'
279            IF( ahtrc0 < 0 .AND. .NOT. lk_esopa ) THEN
280               IF(lwp) WRITE(numout,cform_err)
281               IF(lwp) WRITE(numout,*) 'The horizontal diffusivity coef. aht0 must be positive'
282               nstop = nstop + 1
283            ENDIF
284         ENDIF
285      ENDIF
286
287   END SUBROUTINE trc_ldf_ctl
288
289   SUBROUTINE trc_zdf_ctl
290      !!----------------------------------------------------------------------
291      !!                  ***  ROUTINE trc_zdf_ctl  ***
292      !!
293      !! ** Purpose :     Control the consistency between cpp options for
294      !!      tracer vertical diffusion
295      !!
296      !!   9.0  !  04-03  (C. Ethe) 
297      !!----------------------------------------------------------------------
298      !! * Local declarations
299
300      !!----------------------------------------------------------------------
301      !!  OPA 9.0, LODYC-IPSL (2003)
302      !!----------------------------------------------------------------------
303
304      ! Parameter & key controls
305      ! ------------------------
306      ! ... vertical mixing
307      ! time stepping scheme (N.B. TKE scheme => force the use of implicit scheme)
308#if defined key_zdftke
309      l_trczdf_exp = .FALSE.          ! use implicit scheme
310      l_trczdf_imp = .TRUE. 
311#else
312      IF( ln_zdfexp  ) THEN 
313         l_trczdf_exp = .TRUE.           ! use explicit scheme
314         l_trczdf_imp = .FALSE.
315      ELSE
316         l_trczdf_exp = .FALSE.          ! use implicit scheme
317         l_trczdf_imp = .TRUE. 
318      ENDIF
319#endif
320
321      IF( l_trczdf_iso .OR. l_trczdf_iso_vo ) THEN 
322         l_trczdf_exp = .FALSE.          ! iso-neutral diffusion :
323         l_trczdf_imp = .FALSE.          ! implicit scheme included in iso-neutral routine
324      ENDIF
325
326#if defined key_esopa
327      l_trczdf_exp = .TRUE.           ! esopa: use all options
328      l_trczdf_imp = .TRUE.
329#endif
330
331
332   END SUBROUTINE trc_zdf_ctl
333
334   SUBROUTINE trc_dmp_ctl
335      !!----------------------------------------------------------------------
336      !!                  ***  ROUTINE trc_dmp_ctl  ***
337      !!
338      !! ** Purpose :    Control the consistency between cpp options for
339      !!      tracer newtonian damping
340      !!
341      !!
342      !! History :
343      !!   9.0  !  04-03  (C. Ethe)
344      !!----------------------------------------------------------------------
345#if defined key_trcdmp
346
347      SELECT CASE ( ndmptr )
348
349      CASE ( -1 )               ! ORCA: damping in Red & Med Seas only
350         IF(lwp) WRITE(numout,*) '          tracer damping in the Med & Red seas only'
351
352      CASE ( 1:90 )             ! Damping poleward of 'ndmptr' degrees
353         IF(lwp) WRITE(numout,*) '          tracer damping poleward of', ndmptr, ' degrees'
354
355      CASE DEFAULT
356         IF(lwp) WRITE(numout,cform_err)
357         IF(lwp) WRITE(numout,*) '          bad flag value for ndmptr = ', ndmptr
358         nstop = nstop + 1
359
360      END SELECT
361
362
363      SELECT CASE ( nmldmptr )
364
365      CASE ( 0 )                ! newtonian damping throughout the water column
366         IF(lwp) WRITE(numout,*) '          tracer damping throughout the water column'
367
368      CASE ( 1 )                ! no damping in the turbocline (avt > 5 cm2/s)
369         IF(lwp) WRITE(numout,*) '          no tracer damping in the turbocline'
370
371      CASE ( 2 )                ! no damping in the mixed layer
372         IF(lwp) WRITE(numout,*) '          no tracer damping in the mixed layer'
373
374      CASE DEFAULT
375         IF(lwp) WRITE(numout,cform_err)
376         IF(lwp) WRITE(numout,*) '          bad flag value for nmldmptr = ', nmldmptr
377         nstop = nstop + 1
378
379      END SELECT
380#endif
381 
382   END SUBROUTINE trc_dmp_ctl
383
384#else
385   !!----------------------------------------------------------------------
386   !!   Dummy module :                      NO passive tracer
387   !!----------------------------------------------------------------------
388CONTAINS
389   SUBROUTINE trc_trp_ctl             ! Empty routine
390   END SUBROUTINE trc_trp_ctl
391#endif
392   
393  !!======================================================================
394END MODULE trctrp_ctl
Note: See TracBrowser for help on using the repository browser.