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

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

CL + CT: BUGFIX093: Add missing line "#include "domzgr_substitute.h90" "

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