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 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

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