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

source: branches/DEV_r2191_3partymerge2010/NEMO/OPA_SRC/TRA/traldf.F90 @ 2205

Last change on this file since 2205 was 2205, checked in by acc, 14 years ago

#733 DEV_r2191_3partymerge2010. Merged in changes from DEV_r1924_nocs_latphys

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