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 branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRA – NEMO

source: branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRA/traldf.F90 @ 2034

Last change on this file since 2034 was 2034, checked in by cetlod, 14 years ago

cosmetic changes

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