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

Last change on this file since 627 was 620, checked in by opalod, 17 years ago

nemo_v2_update_005 : CT : allow to run without horizontal diffusion in setting ln_traldf_lap & ln_traldf_bilap logicals to .false.

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