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.
ldftra.F90 in trunk/NEMO/OPA_SRC/LDF – NEMO

source: trunk/NEMO/OPA_SRC/LDF/ldftra.F90 @ 27

Last change on this file since 27 was 27, checked in by opalod, 20 years ago

CT : BUGFIX009 : Running problem for EEL5 configuration is solved

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 12.6 KB
Line 
1MODULE ldftra
2   !!======================================================================
3   !!                       ***  MODULE  ldftra  ***
4   !! Ocean physics:  lateral diffusivity coefficient
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   ldf_tra_init : initialization, namelist read, and parameters control
9   !!   ldf_tra_c3d   : 3D eddy viscosity coefficient initialization
10   !!   ldf_tra_c2d   : 2D eddy viscosity coefficient initialization
11   !!   ldf_tra_c1d   : 1D eddy viscosity coefficient initialization
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE phycst          ! physical constants
17   USE ldftra_oce      ! ocean tracer   lateral physics
18   USE ldfslp          ! ???
19   USE in_out_manager  ! I/O manager
20   USE lib_mpp         ! distribued memory computing library
21   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! *  Routine accessibility
27   PUBLIC ldf_tra_init   ! called by opa.F90
28
29   !! * Substitutions
30#  include "vectopt_loop_substitute.h90"
31   !!---------------------------------------------------------------------------------
32   !!   OPA 9.0 , LODYC-IPSL  (2003)
33   !!---------------------------------------------------------------------------------
34
35CONTAINS
36
37   SUBROUTINE ldf_tra_init
38      !!----------------------------------------------------------------------
39      !!                  ***  ROUTINE ldf_tra_init  ***
40      !!
41      !! ** Purpose :   initializations of the horizontal ocean tracer physics
42      !!
43      !! ** Method :
44      !!      Direction of lateral diffusion (tracers and/or momentum)
45      !!        ln_traldf_iso  = T : initialize the slope arrays to zero
46      !!        ln_traldf_geop = T : initialise the slope arrays to the i- and
47      !!                            j-slopes of s-surfaces
48      !!      Eddy diffusivity and eddy induced velocity cefficients:
49      !!         default option   : constant coef. aht0, aeiv0 (namelist)
50      !!        'key_traldf_c1d': depth dependent coef. defined in
51      !!                            in ldf_tra_c1d routine
52      !!        'key_traldf_c2d': latitude and longitude dependent coef.
53      !!                            defined in ldf_tra_c2d routine
54      !!        'key_traldf_c3d': latitude, longitude, depth dependent coef.
55      !!                            defined in ldf_tra_c3d routine
56      !!
57      !!      N.B. User defined include files.  By default, 3d and 2d coef.
58      !!      are set to a constant value given in the namelist and the 1d
59      !!      coefficients are initialized to a hyperbolic tangent vertical
60      !!      profile.
61      !!
62      !! Reference :
63      !!      Madec, G. and M. Imbard, 1996, A global ocean mesh to overcome
64      !!      the North Pole singularity, Climate Dynamics, 12, 381-388.
65      !!
66      !! History :
67      !!        !  07-97  (G. Madec)  from inimix.F split in 2 routines
68      !!        !  08-97  (G. Madec)  multi dimensional coefficients
69      !!   8.5  !  02-09  (G. Madec)  F90: Free form and module
70      !!----------------------------------------------------------------------
71      !! * Modules used
72      USE ioipsl
73
74      !! * Local declarations
75      INTEGER ::   ioptio               ! ???
76      LOGICAL ::   ll_print = .FALSE.   ! =T print eddy coef. in numout
77       
78      NAMELIST/nam_traldf/ ln_traldf_lap  , ln_traldf_bilap,                &
79         &                 ln_traldf_level, ln_traldf_hor, ln_traldf_iso,   &
80         &                 aht0, ahtb0, aeiv0
81      !!----------------------------------------------------------------------
82
83      !  Define the lateral tracer physics parameters
84      ! =============================================
85   
86      ! Read Namelist nam_traldf : Lateral physics on tracers
87      REWIND( numnam )
88      READ  ( numnam, nam_traldf )
89
90      IF(lwp) THEN
91         WRITE(numout,*)
92         WRITE(numout,*) 'ldf_tra : lateral tracer physics'
93         WRITE(numout,*) '~~~~~~~'
94         WRITE(numout,*) '          Namelist nam_traldf : set lateral mixing parameters (type, direction, coefficients)'
95         WRITE(numout,*) '             laplacian operator          ln_traldf_lap   = ', ln_traldf_lap
96         WRITE(numout,*) '             bilaplacian operator        ln_traldf_bilap = ', ln_traldf_bilap
97         WRITE(numout,*) '             iso-level                   ln_traldf_level = ', ln_traldf_level
98         WRITE(numout,*) '             horizontal (geopotential)   ln_traldf_hor   = ', ln_traldf_hor
99         WRITE(numout,*) '             iso-neutral                 ln_traldf_iso   = ', ln_traldf_iso
100         WRITE(numout,*) '             lateral eddy diffusivity             aht0   = ', aht0
101         WRITE(numout,*) '             background hor. diffusivity          ahtb0  = ', ahtb0
102         WRITE(numout,*) '             eddy induced velocity coef.          aeiv0  = ', aeiv0
103         WRITE(numout,*)
104      ENDIF
105
106      ! Parameter control
107
108      ! control the input
109      ioptio = 0
110      IF( ln_traldf_lap   )   ioptio = ioptio + 1
111      IF( ln_traldf_bilap )   ioptio = ioptio + 1
112      IF( ioptio /= 1 )   THEN
113          IF(lwp) WRITE(numout,cform_err)
114          IF(lwp) WRITE(numout,*) '          use ONE of the 2 lap/bilap operator type on tracer'
115          nstop = nstop + 1
116      ENDIF
117      ioptio = 0
118      IF( ln_traldf_level )   ioptio = ioptio + 1
119      IF( ln_traldf_hor   )   ioptio = ioptio + 1
120      IF( ln_traldf_iso   )   ioptio = ioptio + 1
121      IF( ioptio /= 1 ) THEN
122         IF(lwp) WRITE(numout,cform_err)
123         IF(lwp) WRITE(numout,*) '          use only ONE direction (level/hor/iso)'
124         nstop = nstop + 1
125      ENDIF
126
127      ! ... Choice of the lateral scheme used
128      IF( lk_traldf_eiv ) THEN
129         IF(lwp) WRITE(numout,*) '          eddy induced velocity on tracers'
130            IF( .NOT.ln_traldf_iso .OR. ln_traldf_bilap ) THEN
131            IF(lwp) WRITE(numout,cform_err)
132            IF(lwp) WRITE(numout,*) ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion'
133            nstop = nstop + 1
134         ENDIF
135      ENDIF
136
137      IF( lk_sco ) THEN          ! s-coordinates: rotation required for horizontal or isopycnal mixing
138         IF( ( ln_traldf_iso .OR. ln_traldf_hor ) .AND. .NOT.lk_ldfslp ) THEN
139            IF(lwp) WRITE(numout,cform_err)
140            IF(lwp) WRITE(numout,*) '          the rotation of the diffusive tensor require key_ldfslp'
141            IF( .NOT.lk_esopa )   nstop = nstop + 1
142         ENDIF
143      ELSE                       ! z-coordinates with/without partial step:
144         ln_traldf_level = ln_traldf_level .OR. ln_traldf_hor      ! level diffusion = horizontal diffusion
145         ln_traldf_hor   = .FALSE.
146         IF(lwp) WRITE(numout,*) '          horizontal mixing in z-coord or partial steps: force ln_traldf_level = T'
147         IF(lwp) WRITE(numout,*) '                                                  and    force ln_traldf_hor   = F'
148         IF( ln_traldf_iso .AND. .NOT.lk_ldfslp ) THEN             ! rotation required for isopycnal mixing
149            IF(lwp) WRITE(numout,cform_err)
150            IF(lwp) WRITE(numout,*) '          the rotation of the diffusive tensor require key_ldfslp'
151            IF( .NOT.lk_esopa )   nstop = nstop + 1
152         ENDIF
153      ENDIF
154
155      l_traldf_lap     =       ln_traldf_lap   .AND. ln_traldf_level     ! iso-level   laplacian operator
156      l_traldf_bilap   =       ln_traldf_bilap .AND. ln_traldf_level     ! iso-level bilaplacian operator
157      l_traldf_bilapg  =       ln_traldf_bilap .AND. ln_traldf_hor       ! geopotential bilap. (s-coord)
158      l_traldf_iso     =       ln_traldf_lap   .AND.                  &  ! laplacian operator
159         &                   ( ln_traldf_iso   .OR.  ln_traldf_hor )  &  ! iso-neutral (z-coord) or horizontal (s-coord)
160         &                                     .AND. .NOT.lk_zps
161      l_traldf_iso_zps =       ln_traldf_lap   .AND.                  &  ! laplacian operator
162         &                   ( ln_traldf_iso   .OR.  ln_traldf_hor )  &  ! iso-neutral (partial steps)
163         &                                     .AND. lk_zps              ! or geopotential in mixed partial steps/s-coord
164      l_trazdf_iso    = .FALSE.
165      l_trazdf_iso_vo = .FALSE.
166      IF( l_traldf_iso     )   l_trazdf_iso = .TRUE.
167      IF( l_traldf_iso_zps )   l_trazdf_iso = .TRUE.
168#if defined key_vectopt_memory
169      IF( l_trazdf_iso ) THEN
170         l_trazdf_iso    = .FALSE.
171         l_trazdf_iso_vo = .TRUE.
172      ENDIF
173#endif
174
175      ioptio = 0
176      IF( l_traldf_lap     )   ioptio = ioptio + 1
177      IF( l_traldf_bilap   )   ioptio = ioptio + 1
178      IF( l_traldf_bilapg  )   ioptio = ioptio + 1
179      IF( l_traldf_iso     )   ioptio = ioptio + 1
180      IF( l_traldf_iso_zps )   ioptio = ioptio + 1
181      IF( ioptio /= 1 ) THEN
182         IF(lwp) WRITE(numout,cform_err)
183         IF(lwp) WRITE(numout,*) '          this combination of operator and direction has not been implemented'
184         nstop = nstop + 1
185      ENDIF
186      IF( lk_esopa ) THEN
187         l_traldf_lap = .TRUE.   ;   l_traldf_bilap   = .TRUE.   ;   l_traldf_bilapg  = .TRUE.
188         l_traldf_iso = .TRUE.   ;   l_traldf_iso_zps = .TRUE.
189         l_trazdf_iso = .TRUE.   ;   l_trazdf_iso_vo  = .TRUE.
190         IF(lwp ) WRITE(numout,*) '          esopa test: use all lateral physics options'
191      ENDIF
192
193
194      ! ... Space variation of eddy coefficients
195      ioptio = 0
196#if defined key_traldf_c3d
197      IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude, depth)'
198      ioptio = ioptio + 1
199#endif
200#if defined key_traldf_c2d
201      IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude)'
202      ioptio = ioptio + 1
203#endif
204#if defined key_traldf_c1d
205      IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( depth )'
206      ioptio = ioptio + 1
207      IF( lk_sco ) THEN
208         IF(lwp) WRITE(numout,cform_err)
209         IF(lwp) WRITE(numout,*) '          key_traldf_c1d cannot be used in s-coordinate (key_s_coord)'
210         nstop = nstop + 1
211      ENDIF
212#endif
213      IF( ioptio == 0 ) THEN
214          IF(lwp) WRITE(numout,*) '          tracer mixing coef. = constant (default option)'
215        ELSEIF( ioptio > 1 ) THEN
216          IF(lwp) WRITE(numout,cform_err)
217          IF(lwp) WRITE(numout,*) '          use only one of the following keys:',   &
218             &                    ' key_traldf_c3d, key_traldf_c2d, key_traldf_c1d'
219          nstop = nstop + 1
220      ENDIF
221
222      IF( l_traldf_bilap .OR. l_traldf_bilapg ) THEN
223         IF(lwp) WRITE(numout,*) '          biharmonic tracer diffusion'
224         IF( aht0 > 0 .AND. .NOT. lk_esopa ) THEN
225            IF(lwp) WRITE(numout,cform_err)
226            IF(lwp) WRITE(numout,*) '          The horizontal diffusivity coef. aht0 must be negative'
227            nstop = nstop + 1
228         ENDIF
229      ELSE
230         IF(lwp) WRITE(numout,*) '          harmonic tracer diffusion (default)'
231         IF( aht0 < 0 .AND. .NOT. lk_esopa ) THEN
232            IF(lwp) WRITE(numout,cform_err)
233            IF(lwp) WRITE(numout,*) '          The horizontal diffusivity coef. aht0 must be positive'
234            nstop = nstop + 1
235         ENDIF
236      ENDIF
237
238
239      !  Lateral eddy diffusivity and eddy induced velocity coefficients
240      ! ================================================================
241
242#if defined key_traldf_c3d
243      CALL ldf_tra_c3d( ll_print )           ! aht = 3D coef. = F( longitude, latitude, depth )
244#elif defined key_traldf_c2d
245      CALL ldf_tra_c2d( ll_print )           ! aht = 2D coef. = F( longitude, latitude )
246#elif defined key_traldf_c1d
247      CALL ldf_tra_c1d( ll_print )           ! aht = 1D coef. = F( depth )
248#else
249                                     ! Constant coefficients
250      IF(lwp)WRITE(numout,*)
251      IF(lwp)WRITE(numout,*) ' inildf: constant eddy diffusivity coef.'
252      IF(lwp)WRITE(numout,*) ' ~~~~~~'
253      IF(lwp)WRITE(numout,*) '        ahtu = ahtv = ahtw = aht0 = ', aht0
254      IF( lk_traldf_eiv ) THEN
255         IF(lwp)WRITE(numout,*)
256         IF(lwp)WRITE(numout,*) ' inildf: constant eddy induced velocity coef.'
257         IF(lwp)WRITE(numout,*) ' ~~~~~~  '
258         IF(lwp)WRITE(numout,*) '         aeiu = aeiv = aeiw = aeiv0 = ', aeiv0
259      ENDIF
260#endif
261
262   END SUBROUTINE ldf_tra_init
263
264#if defined key_traldf_c3d
265#   include "ldftra_c3d.h90"
266#elif defined key_traldf_c2d
267#   include "ldftra_c2d.h90"
268#elif defined key_traldf_c1d
269#   include "ldftra_c1d.h90"
270#endif
271
272   !!======================================================================
273END MODULE ldftra
Note: See TracBrowser for help on using the repository browser.