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

source: trunk/NEMO/OPA_SRC/TRA/traldf.F90 @ 473

Last change on this file since 473 was 458, checked in by opalod, 18 years ago

nemo_v1_update_049:RB: reorganization of tracers part, remove traadv_cen2_atsk.h90 traldf_iso_zps.F90 trazdf_iso.F90 trazdf_iso_vopt.F90, change atsk routines to jki, add control modules traadv, traldf, trazdf

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 16.2 KB
Line 
1MODULE traldf
2   !!======================================================================
3   !!                       ***  MODULE  traldf  ***
4   !! Ocean Active tracers : lateral diffusive trends
5   !!=====================================================================
6   !! History :
7   !!   9.0  !  05-11  (G. Madec)  Original code
8   !!----------------------------------------------------------------------
9   !!   tra_ldf     : update the tracer trend with the lateral diffusion
10   !!       ldf_ctl : initialization, namelist read, and parameters control
11   !!       ldf_ano : compute lateral diffusion for constant T-S profiles
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 traldf_bilapg   ! lateral mixing            (tra_ldf_bilapg routine)
20   USE traldf_bilap    ! lateral mixing             (tra_ldf_bilap routine)
21   USE traldf_iso      ! lateral mixing               (tra_ldf_iso routine)
22   USE traldf_lap      ! lateral mixing               (tra_ldf_lap routine)
23   USE trdmod          ! ocean active tracers trends
24   USE trdmod_oce      ! ocean variables trends
25   USE prtctl          ! Print control
26   USE in_out_manager  ! I/O manager
27   USE lib_mpp         ! distribued memory computing library
28   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
29
30   IMPLICIT NONE
31   PRIVATE
32
33   !! *  Routine accessibility
34   PUBLIC tra_ldf      ! called by step.F90
35
36   !! * module variables
37   INTEGER ::                        & 
38      nldf = 0                         ! type of lateral diffusion used
39      !                                ! defined from ln_traldf_... namlist logicals)
40#if defined key_traldf_ano
41   REAL, DIMENSION(jpi,jpj,jpk) ::   & 
42      t0_ldf, s0_ldf                    ! lateral diffusion trends of T & S
43      !                                 ! for a constant vertical profile
44#endif
45
46   !! * Substitutions
47#  include "domzgr_substitute.h90"
48#  include "vectopt_loop_substitute.h90"
49   !!---------------------------------------------------------------------------------
50   !!   OPA 9.0 , LOCEAN-IPSL (2005)
51   !!---------------------------------------------------------------------------------
52
53CONTAINS
54
55   SUBROUTINE tra_ldf( kt )
56      !!----------------------------------------------------------------------
57      !!                  ***  ROUTINE tra_ldf  ***
58      !!
59      !! ** Purpose :   compute the lateral ocean tracer physics.
60      !!
61      !!----------------------------------------------------------------------
62      !! * Arguments
63      INTEGER, INTENT( in ) ::   kt     ! ocean time-step index
64
65      !! * local declarations
66      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
67         ztrdt, ztrds                         ! 3D temporary workspace
68      !!----------------------------------------------------------------------
69
70      IF( kt == nit000 )   CALL ldf_ctl      ! initialisation & control of options
71
72      IF( l_trdtra )   THEN                      ! temporary save of ta and sa trends
73         ztrdt(:,:,:) = ta(:,:,:) 
74         ztrds(:,:,:) = sa(:,:,:) 
75      ENDIF
76
77      SELECT CASE ( nldf )                       ! compute lateral mixing trend and add it to the general trend
78      CASE ( -1 )                                       ! esopa: test all possibility with control print
79         CALL tra_ldf_lap    ( kt )
80         CALL prt_ctl( tab3d_1=ta, clinfo1=' ldf0 - Ta: ', mask1=tmask,               &
81            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
82         CALL tra_ldf_iso    ( kt )
83         CALL prt_ctl( tab3d_1=ta, clinfo1=' ldf1 - Ta: ', mask1=tmask,               &
84            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
85         CALL tra_ldf_bilap  ( kt )
86         CALL prt_ctl( tab3d_1=ta, clinfo1=' ldf2 - Ta: ', mask1=tmask,               &
87            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
88         CALL tra_ldf_bilapg ( kt )
89         CALL prt_ctl( tab3d_1=ta, clinfo1=' ldf3 - Ta: ', mask1=tmask,               &
90            &          tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
91
92      CASE ( 0 )                                       ! iso-level laplacian
93         CALL tra_ldf_lap    ( kt )
94      CASE ( 1 )                                       ! rotated laplacian (except dk[ dk[.] ] part)
95         CALL tra_ldf_iso    ( kt )
96      CASE ( 2 )                                       ! iso-level bilaplacian
97         CALL tra_ldf_bilap  ( kt )
98      CASE ( 3 )                                       ! s-coord. horizontal bilaplacian
99         CALL tra_ldf_bilapg ( kt )
100      END SELECT
101
102#if defined key_traldf_ano
103      !                                          ! anomaly: substract the reference diffusivity
104      ta(:,:,:) = ta(:,:,:) - t0_ldf(:,:,:)
105      sa(:,:,:) = sa(:,:,:) - s0_ldf(:,:,:)
106#endif
107
108      !                                          ! save the horizontal diffusive trends for further diagnostics
109      IF( l_trdtra )   THEN
110         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
111         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
112         CALL trd_mod( ztrdt, ztrds, jpttdldf, 'TRA', kt )
113      ENDIF
114
115      !                                          ! print mean trends (used for debugging)
116      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' ldf  - Ta: ', mask1=tmask,               &
117         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
118
119   END SUBROUTINE tra_ldf
120
121
122   SUBROUTINE ldf_ctl
123      !!----------------------------------------------------------------------
124      !!                  ***  ROUTINE ldf_ctl  ***
125      !!
126      !! ** Purpose :   Choice of the operator for the lateral tracer diffusion
127      !!
128      !! ** Method  :   set nldf from the nam_traldf logicals
129      !!      nldf == -1   ESOPA test: ALL operators are used
130      !!      nldf ==  0   laplacian operator
131      !!      nldf ==  1   Rotated laplacian operator
132      !!      nldf ==  2   bilaplacian operator
133      !!      nldf ==  3   Rotated bilaplacian
134      !!
135      !!----------------------------------------------------------------------
136      !! * Local declarations
137      INTEGER ::   ioptio, ierr         ! temporary integers
138!     
139!     NAMELIST/nam_traldf/ ln_traldf_lap  , ln_traldf_bilap,                &
140!        &                 ln_traldf_level, ln_traldf_hor, ln_traldf_iso,   &
141!        &                 aht0, ahtb0, aeiv0
142      !!----------------------------------------------------------------------
143
144      !  Define the lateral mixing oparator for tracers
145      ! ===============================================
146   
147      ! Namelist nam_traldf already read in ldftra module
148!     ! Read Namelist nam_traldf : Lateral physics on tracers
149!     REWIND( numnam )
150!     READ  ( numnam, nam_traldf )
151
152      IF(lwp) THEN
153         WRITE(numout,*)
154         WRITE(numout,*) 'tra:ldf_ctl : lateral tracer diffusive operator'
155         WRITE(numout,*) '~~~~~~~~~~~'
156         WRITE(numout,*) '          Namelist nam_traldf : set lateral mixing parameters (type, direction, coefficients)'
157         WRITE(numout,*) '             laplacian operator          ln_traldf_lap   = ', ln_traldf_lap
158         WRITE(numout,*) '             bilaplacian operator        ln_traldf_bilap = ', ln_traldf_bilap
159         WRITE(numout,*) '             iso-level                   ln_traldf_level = ', ln_traldf_level
160         WRITE(numout,*) '             horizontal (geopotential)   ln_traldf_hor   = ', ln_traldf_hor
161         WRITE(numout,*) '             iso-neutral                 ln_traldf_iso   = ', ln_traldf_iso
162      ENDIF
163
164      ! Parameter control
165
166      ! control the input
167      ioptio = 0
168      IF( ln_traldf_lap   )   ioptio = ioptio + 1
169      IF( ln_traldf_bilap )   ioptio = ioptio + 1
170      IF( ioptio /= 1 )   THEN
171          IF(lwp) WRITE(numout,cform_err)
172          IF(lwp) WRITE(numout,*) '          use ONE of the 2 lap/bilap operator type on tracer'
173          nstop = nstop + 1
174      ENDIF
175      ioptio = 0
176      IF( ln_traldf_level )   ioptio = ioptio + 1
177      IF( ln_traldf_hor   )   ioptio = ioptio + 1
178      IF( ln_traldf_iso   )   ioptio = ioptio + 1
179      IF( ioptio /= 1 ) THEN
180         IF(lwp) WRITE(numout,cform_err)
181         IF(lwp) WRITE(numout,*) '          use only ONE direction (level/hor/iso)'
182         nstop = nstop + 1
183      ENDIF
184
185      ! defined the type of lateral diffusion from ln_traldf_... logicals
186      ierr = 0
187      IF ( ln_traldf_lap ) THEN      ! laplacian operator
188         IF ( ln_zco ) THEN                ! z-coordinate
189            IF ( ln_traldf_level )   nldf = 0      ! iso-level  (no rotation)
190            IF ( ln_traldf_hor   )   nldf = 0      ! horizontal (no rotation)
191            IF ( ln_traldf_iso   )   nldf = 1      ! isoneutral (   rotation)
192         ENDIF
193         IF ( ln_zps ) THEN             ! z-coordinate
194            IF ( ln_traldf_level )   ierr = 1      ! iso-level not allowed
195            IF ( ln_traldf_hor   )   nldf = 0      ! horizontal (no rotation)
196            IF ( ln_traldf_iso   )   nldf = 1      ! isoneutral (   rotation)
197         ENDIF
198         IF ( ln_sco ) THEN             ! z-coordinate
199            IF ( ln_traldf_level )   nldf = 0      ! iso-level  (no rotation)
200            IF ( ln_traldf_hor   )   nldf = 1      ! horizontal (   rotation)
201            IF ( ln_traldf_iso   )   nldf = 1      ! isoneutral (   rotation)
202         ENDIF
203      ENDIF
204
205      IF( ln_traldf_bilap ) THEN      ! bilaplacian operator
206         IF ( ln_zco ) THEN                ! z-coordinate
207            IF ( ln_traldf_level )   nldf = 2      ! iso-level  (no rotation)
208            IF ( ln_traldf_hor   )   nldf = 2      ! horizontal (no rotation)
209            IF ( ln_traldf_iso   )   ierr = 2      ! isoneutral (   rotation)
210         ENDIF
211         IF ( ln_zps ) THEN             ! z-coordinate
212            IF ( ln_traldf_level )   ierr = 1      ! iso-level not allowed
213            IF ( ln_traldf_hor   )   nldf = 2      ! horizontal (no rotation)
214            IF ( ln_traldf_iso   )   ierr = 2      ! isoneutral (   rotation)
215         ENDIF
216         IF ( ln_sco ) THEN             ! z-coordinate
217            IF ( ln_traldf_level )   nldf = 2      ! iso-level  (no rotation)
218            IF ( ln_traldf_hor   )   nldf = 3      ! horizontal (   rotation)
219            IF ( ln_traldf_iso   )   ierr = 2      ! isoneutral (   rotation)
220         ENDIF
221      ENDIF
222
223      IF( ierr == 1 ) THEN
224         IF(lwp) WRITE(numout,cform_err)
225         IF(lwp) WRITE(numout,*) ' iso-level in z-coordinate - partial step, not allowed'
226         nstop = nstop + 1
227      ENDIF
228      IF( ierr == 2 ) THEN
229         IF(lwp) WRITE(numout,cform_err)
230         IF(lwp) WRITE(numout,*) ' isoneutral bilaplacian operator does not exist'
231         nstop = nstop + 1
232      ENDIF
233      IF( lk_traldf_eiv .AND. .NOT.ln_traldf_iso ) THEN
234         IF(lwp) WRITE(numout,*) '          eddy induced velocity on tracers'
235         IF(lwp) WRITE(numout,cform_err)
236         IF(lwp) WRITE(numout,*) ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion'
237         nstop = nstop + 1
238      ENDIF
239      IF( nldf == 1 .OR. nldf == 3 ) THEN      ! rotation
240         IF( .NOT.lk_ldfslp ) THEN
241            IF(lwp) WRITE(numout,cform_err)
242            IF(lwp) WRITE(numout,*) '          the rotation of the diffusive tensor require key_ldfslp'
243            nstop = nstop + 1
244         ENDIF
245      ENDIF
246
247      IF( lk_esopa ) THEN
248         IF(lwp) WRITE(numout,*) '          esopa control: use all lateral physics options'
249         nldf = -1
250      ENDIF
251
252      IF(lwp) THEN
253         WRITE(numout,*)
254         IF( nldf == -1 )   WRITE(numout,*) '              ESOPA test All scheme used'
255         IF( nldf ==  0 )   WRITE(numout,*) '              laplacian operator'
256         IF( nldf ==  1 )   WRITE(numout,*) '              Rotated laplacian operator'
257         IF( nldf ==  2 )   WRITE(numout,*) '              bilaplacian operator'
258         IF( nldf ==  3 )   WRITE(numout,*) '              Rotated bilaplacian'
259      ENDIF
260
261
262      ! Reference T & S diffusivity (if necessary)
263      ! ===========================
264
265      CALL ldf_ano
266
267   END SUBROUTINE ldf_ctl
268
269#if defined key_traldf_ano
270   !!----------------------------------------------------------------------
271   !!   'key_traldf_ano'               T & S lateral diffusion on anomalies
272   !!----------------------------------------------------------------------
273
274   SUBROUTINE ldf_ano
275      !!----------------------------------------------------------------------
276      !!                  ***  ROUTINE ldf_ano  ***
277      !!
278      !! ** Purpose :   initializations of
279      !!
280      !!----------------------------------------------------------------------
281      !! * Modules used
282      USE zdf_oce         ! vertical mixing
283      USE trazdf          ! vertical mixing: double diffusion
284      USE zdfddm          ! vertical mixing: double diffusion
285
286      !! * local declarations
287      INTEGER  ::   jk                         ! Dummy loop indice
288      LOGICAL  ::   llsave                     !
289      REAL(wp) ::   zt0, zs0, z12              ! temporary scalar
290      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
291         zt_ref, ztb, zavt,                 &  ! 3D temporary workspace
292         zs_ref, zsb                           ! 3D temporary workspace
293      !!----------------------------------------------------------------------
294
295      IF(lwp) THEN
296         WRITE(numout,*)
297         WRITE(numout,*) 'tra:ldf_ano : lateral diffusion acting on anomalies'
298         WRITE(numout,*) '~~~~~~~~~~~'
299      ENDIF
300
301      ! defined the T & S reference profiles
302      ! ------------------------------------
303      zt0 =10.e0                               ! homogeneous ocean
304      zs0 =35.e0
305      zt_ref(:,:,:) = 10.0 * tmask(:,:,:)
306      zs_ref(:,:,:) = 35.0 * tmask(:,:,:)
307      IF(lwp) WRITE(numout,*) '              homogeneous ocean T = ', zt0, ' S = ',zs0
308
309      !                                        ! T & S profile (to be coded +namelist parameter
310
311      ! prepare the ldf computation
312      ! ---------------------------
313      llsave = l_trdtra
314      l_trdtra = .false.      ! desactivate trend computation
315      t0_ldf(:,:,:) = 0.e0
316      s0_ldf(:,:,:) = 0.e0
317      ztb   (:,:,:) = tb (:,:,:)
318      zsb   (:,:,:) = sb (:,:,:)
319      ua    (:,:,:) = ta (:,:,:)
320      va    (:,:,:) = sa (:,:,:)
321      zavt  (:,:,:) = avt(:,:,:)
322      IF( lk_zdfddm ) THEN
323          IF(lwp) WRITE(numout,cform_err)
324          IF(lwp) WRITE(numout,*) ' key_traldf_ano with key_zdfddm not implemented'
325          nstop = nstop + 1
326      ENDIF
327      ! set tb, sb to reference values and avr to zero
328      tb (:,:,:) = zt_ref(:,:,:)
329      sb (:,:,:) = zs_ref(:,:,:)
330      ta (:,:,:) = 0.e0
331      sa (:,:,:) = 0.e0
332      avt(:,:,:) = 0.e0
333
334      ! Compute the ldf trends
335      ! ----------------------
336      CALL tra_ldf( nit000+1 )      ! horizontal components (+1: no more init)
337      CALL tra_zdf( nit000   )      ! vertical component (if necessary nit000 to performed the init)
338
339      ! finalise the computation and recover all arrays
340      ! -----------------------------------------------
341      l_trdtra = llsave
342      z12 = 2.e0
343      IF( neuler == 1)   z12 = 1.e0
344      IF( ln_zdfexp ) THEN      ! ta,sa are the trends
345         t0_ldf(:,:,:) = ta(:,:,:)
346         s0_ldf(:,:,:) = sa(:,:,:)
347      ELSE
348         DO jk = 1, jpkm1
349            t0_ldf(:,:,jk) = ( ta(:,:,jk) - tb(:,:,jk) ) / ( z12 *rdttra(jk) )
350            s0_ldf(:,:,jk) = ( sa(:,:,jk) - tb(:,:,jk) ) / ( z12 *rdttra(jk) )
351         END DO
352      ENDIF
353      tb    (:,:,:) = ztb (:,:,:)
354      sb    (:,:,:) = zsb (:,:,:)
355      ta    (:,:,:) = ua  (:,:,:)
356      sa    (:,:,:) = va  (:,:,:)
357      avt   (:,:,:) = zavt(:,:,:)
358
359   END SUBROUTINE ldf_ano
360
361#else
362   !!----------------------------------------------------------------------
363   !!   default option :   Dummy code   NO T & S background profiles
364   !!----------------------------------------------------------------------
365   SUBROUTINE ldf_ano
366      IF(lwp) THEN
367         WRITE(numout,*)
368         WRITE(numout,*) 'tra:ldf_ano : lateral diffusion acting on the full fields'
369         WRITE(numout,*) '~~~~~~~~~~~'
370      ENDIF
371   END SUBROUTINE ldf_ano
372#endif
373
374   !!======================================================================
375END MODULE traldf
Note: See TracBrowser for help on using the repository browser.