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

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

CL : Add CVS Header and CeCILL licence information

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