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

Last change on this file since 941 was 941, checked in by cetlod, 16 years ago

phasing the passive tracer transport module to the new version of NEMO, see ticket 143

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