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/UKMO/dev_r5518_GO6_starthour_obsoper/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/UKMO/dev_r5518_GO6_starthour_obsoper/NEMOGCM/NEMO/OPA_SRC/TRA/traldf.F90 @ 15603

Last change on this file since 15603 was 15603, checked in by mattmartin, 3 years ago

Updated NEMO branch for coupled NWP at GO6 to include stochastic model perturbations.
For more info see ticket: https://code.metoffice.gov.uk/trac/nwpscience/ticket/1125.

File size: 19.9 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   !!   tra_ldf_init : 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_iso_grif ! lateral mixing          (tra_ldf_iso_grif routine)
24   USE traldf_lap      ! lateral mixing               (tra_ldf_lap routine)
25   USE trd_oce         ! trends: ocean variables
26   USE trdtra          ! trends manager: tracers
27   !
28   USE prtctl          ! Print control
29   USE in_out_manager  ! I/O manager
30   USE lib_mpp         ! distribued memory computing library
31   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
32   USE wrk_nemo        ! Memory allocation
33   USE timing          ! Timing
34   USE stopack
35
36   IMPLICIT NONE
37   PRIVATE
38
39   PUBLIC   tra_ldf        ! called by step.F90
40   PUBLIC   tra_ldf_init   ! called by opa.F90
41   !
42   INTEGER ::   nldf = 0   ! type of lateral diffusion used defined from ln_traldf_... namlist logicals)
43
44   REAL, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   t0_ldf, s0_ldf   !: lateral diffusion trends of T & S for a cst profile
45   !                                                               !  (key_traldf_ano only)
46#if defined key_traldf_c3d
47   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:,:) :: ahtu0, ahtv0, ahtw0, ahtt0
48#endif
49#if defined key_traldf_c2d
50   REAL(wp), SAVE, ALLOCATABLE, DIMENSION(:,:  ) :: ahtu0, ahtv0, ahtw0, ahtt0
51#endif
52
53   !! * Substitutions
54#  include "domzgr_substitute.h90"
55#  include "vectopt_loop_substitute.h90"
56   !!----------------------------------------------------------------------
57   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
58   !! $Id$
59   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
60   !!----------------------------------------------------------------------
61CONTAINS
62
63   SUBROUTINE tra_ldf( kt )
64      !!----------------------------------------------------------------------
65      !!                  ***  ROUTINE tra_ldf  ***
66      !!
67      !! ** Purpose :   compute the lateral ocean tracer physics.
68      !!----------------------------------------------------------------------
69      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
70      !!
71      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdt, ztrds
72      !!----------------------------------------------------------------------
73      !
74      IF( nn_timing == 1 )  CALL timing_start('tra_ldf')
75      !
76      rldf = 1     ! For active tracers the
77      r_fact_lap(:,:,:) = 1.0
78
79      IF( l_trdtra )   THEN                    !* Save ta and sa trends
80         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds ) 
81         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) 
82         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
83      ENDIF
84
85#if defined key_traldf_c3d
86         IF(  ( kt == nit000 ) .AND. &
87            & ( ln_stopack )   .AND. &
88            & ( ( nn_spp_ahtu + nn_spp_ahtv + nn_spp_ahtw + nn_spp_ahtt ) > 0 ) ) THEN
89             ALLOCATE ( ahtu0(jpi,jpj,jpk), ahtv0(jpi,jpj,jpk) )
90             ALLOCATE ( ahtt0(jpi,jpj,jpk), ahtw0(jpi,jpj,jpk) )
91             ahtu0 = ahtu
92             ahtv0 = ahtv
93             ahtw0 = ahtw
94             ahtt0 = ahtt
95         ENDIF
96#endif
97#if defined key_traldf_c2d
98         IF(  ( kt == nit000 ) .AND. &
99            & ( ln_stopack )   .AND. &
100            & ( ( nn_spp_ahtu + nn_spp_ahtv + nn_spp_ahtw + nn_spp_ahtt ) > 0 ) ) THEN
101             ALLOCATE ( ahtu0(jpi,jpj), ahtv0(jpi,jpj) )
102             ALLOCATE ( ahtt0(jpi,jpj), ahtw0(jpi,jpj) )
103             ahtu0 = ahtu
104             ahtv0 = ahtv
105             ahtw0 = ahtw
106             ahtt0 = ahtt
107         ENDIF
108#endif
109#if defined key_traldf_c3d || defined key_traldf_c2d
110         IF( ln_stopack .AND. ( nn_spp_ahtu > 0 ) ) THEN
111             ahtu = ahtu0
112             CALL spp_aht(kt, ahtu, nn_spp_ahtu, rn_ahtu_sd, jk_spp_ahtu)
113         ENDIF
114         IF( ln_stopack .AND. ( nn_spp_ahtv > 0 ) ) THEN
115             ahtv = ahtv0
116             CALL spp_aht(kt, ahtv, nn_spp_ahtv, rn_ahtv_sd, jk_spp_ahtv)
117         ENDIF
118         IF( ln_stopack .AND. ( nn_spp_ahtw > 0 ) ) THEN
119             ahtw = ahtw0
120             CALL spp_aht(kt, ahtw, nn_spp_ahtw, rn_ahtw_sd, jk_spp_ahtw)
121         ENDIF
122         IF( ln_stopack .AND. ( nn_spp_ahtt > 0 ) ) THEN
123             ahtt = ahtt0
124             CALL spp_aht(kt, ahtt, nn_spp_ahtt, rn_ahtt_sd, jk_spp_ahtt)
125         ENDIF
126#endif
127
128      SELECT CASE ( nldf )                       ! compute lateral mixing trend and add it to the general trend
129      CASE ( 0 )   ;   CALL tra_ldf_lap     ( kt, nit000, 'TRA', gtsu, gtsv, gtui, gtvi,        &
130                               &                                   tsb, tsa, jpts        )  ! iso-level laplacian
131      CASE ( 1 )                                                                              ! rotated laplacian
132         IF( ln_traldf_grif ) THEN                                                         
133                       CALL tra_ldf_iso_grif( kt, nit000,'TRA', gtsu, gtsv, tsb, tsa, jpts, ahtb0 )      ! Griffies operator
134         ELSE                                                                               
135                       CALL tra_ldf_iso     ( kt, nit000, 'TRA', gtsu, gtsv, gtui, gtvi,        &
136                               &                                  tsb, tsa, jpts, ahtb0 )      ! Madec operator
137         ENDIF
138      CASE ( 2 )   ;   CALL tra_ldf_bilap   ( kt, nit000, 'TRA', gtsu, gtsv, gtui, gtvi,        &
139                               &                                   tsb, tsa, jpts        )  ! iso-level bilaplacian
140      CASE ( 3 )   ;   CALL tra_ldf_bilapg  ( kt, nit000, 'TRA',             tsb, tsa, jpts        )  ! s-coord. geopot. bilap.
141         !
142      CASE ( -1 )                                ! esopa: test all possibility with control print
143         CALL tra_ldf_lap   ( kt, nit000, 'TRA', gtsu, gtsv, gtui, gtvi,        &
144         &                                       tsb, tsa, jpts        ) 
145         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf0 - Ta: ', mask1=tmask,               &
146         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
147         IF( ln_traldf_grif ) THEN
148            CALL tra_ldf_iso_grif( kt, nit000, 'TRA', gtsu, gtsv, tsb, tsa, jpts, ahtb0 )
149         ELSE
150            CALL tra_ldf_iso     ( kt, nit000, 'TRA', gtsu, gtsv, gtui, gtvi,        &
151            &                                               tsb, tsa, jpts, ahtb0 ) 
152         ENDIF
153         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf1 - Ta: ', mask1=tmask,               &
154         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
155         CALL tra_ldf_bilap ( kt, nit000, 'TRA', gtsu, gtsv, gtui, gtvi,        &
156         &                                       tsb, tsa, jpts        ) 
157         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf2 - Ta: ', mask1=tmask,               &
158         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
159         CALL tra_ldf_bilapg( kt, nit000, 'TRA',             tsb, tsa, jpts        ) 
160         CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf3 - Ta: ', mask1=tmask,               &
161         &             tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
162      END SELECT
163
164#if defined key_traldf_ano
165      tsa(:,:,:,jp_tem) = tsa(:,:,:,jp_tem) - t0_ldf(:,:,:)      ! anomaly: substract the reference diffusivity
166      tsa(:,:,:,jp_sal) = tsa(:,:,:,jp_sal) - s0_ldf(:,:,:)
167#endif
168
169      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
170         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
171         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
172         CALL trd_tra( kt, 'TRA', jp_tem, jptra_ldf, ztrdt )
173         CALL trd_tra( kt, 'TRA', jp_sal, jptra_ldf, ztrds )
174         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
175      ENDIF
176      !                                          ! print mean trends (used for debugging)
177      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' ldf  - Ta: ', mask1=tmask,               &
178         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
179      !
180      IF( nn_timing == 1 )  CALL timing_stop('tra_ldf')
181      !
182   END SUBROUTINE tra_ldf
183
184
185   SUBROUTINE tra_ldf_init
186      !!----------------------------------------------------------------------
187      !!                  ***  ROUTINE tra_ldf_init  ***
188      !!
189      !! ** Purpose :   Choice of the operator for the lateral tracer diffusion
190      !!
191      !! ** Method  :   set nldf from the namtra_ldf logicals
192      !!      nldf == -1   ESOPA test: ALL operators are used
193      !!      nldf ==  0   laplacian operator
194      !!      nldf ==  1   Rotated laplacian operator
195      !!      nldf ==  2   bilaplacian operator
196      !!      nldf ==  3   Rotated bilaplacian
197      !!----------------------------------------------------------------------
198      INTEGER ::   ioptio, ierr         ! temporary integers
199      !!----------------------------------------------------------------------
200
201      !  Define the lateral mixing oparator for tracers
202      ! ===============================================
203   
204      IF(lwp) THEN                    ! Namelist print
205         WRITE(numout,*)
206         WRITE(numout,*) 'tra_ldf_init : lateral tracer diffusive operator'
207         WRITE(numout,*) '~~~~~~~~~~~'
208         WRITE(numout,*) '   Namelist namtra_ldf already read in ldftra module'
209         WRITE(numout,*) '   see ldf_tra_init report for lateral mixing parameters'
210         WRITE(numout,*)
211         IF(lflush) CALL flush(numout)
212      ENDIF
213
214      !                               ! control the input
215      ioptio = 0
216      IF( ln_traldf_lap   )   ioptio = ioptio + 1
217      IF( ln_traldf_bilap )   ioptio = ioptio + 1
218      IF( ioptio >  1 )   CALL ctl_stop( '          use ONE or NONE of the 2 lap/bilap operator type on tracer' )
219      IF( ioptio == 0 )   nldf = -2   ! No lateral diffusion
220      ioptio = 0
221      IF( ln_traldf_level )   ioptio = ioptio + 1
222      IF( ln_traldf_hor   )   ioptio = ioptio + 1
223      IF( ln_traldf_iso   )   ioptio = ioptio + 1
224      IF( ioptio >  1 )   CALL ctl_stop( '          use only ONE direction (level/hor/iso)' )
225
226      ! defined the type of lateral diffusion from ln_traldf_... logicals
227      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully
228      ierr = 0
229      IF( ln_traldf_lap ) THEN       ! laplacian operator
230         IF ( ln_zco ) THEN                ! z-coordinate
231            IF ( ln_traldf_level )   nldf = 0      ! iso-level  (no rotation)
232            IF ( ln_traldf_hor   )   nldf = 0      ! horizontal (no rotation)
233            IF ( ln_traldf_iso   )   nldf = 1      ! isoneutral (   rotation)
234         ENDIF
235         IF ( ln_zps ) THEN             ! zps-coordinate
236            IF ( ln_traldf_level )   ierr = 1      ! iso-level not allowed
237            IF ( ln_traldf_hor   )   nldf = 0      ! horizontal (no rotation)
238            IF ( ln_traldf_iso   )   nldf = 1      ! isoneutral (   rotation)
239         ENDIF
240         IF ( ln_sco ) THEN             ! s-coordinate
241            IF ( ln_traldf_level )   nldf = 0      ! iso-level  (no rotation)
242            IF ( ln_traldf_hor   )   nldf = 1      ! horizontal (   rotation)
243            IF ( ln_traldf_iso   )   nldf = 1      ! isoneutral (   rotation)
244         ENDIF
245      ENDIF
246
247      IF( ln_traldf_bilap ) THEN      ! bilaplacian operator
248         IF ( ln_zco ) THEN                ! z-coordinate
249            IF ( ln_traldf_level )   nldf = 2      ! iso-level  (no rotation)
250            IF ( ln_traldf_hor   )   nldf = 2      ! horizontal (no rotation)
251            IF ( ln_traldf_iso   )   ierr = 2      ! isoneutral (   rotation)
252         ENDIF
253         IF ( ln_zps ) THEN             ! zps-coordinate
254            IF ( ln_traldf_level )   ierr = 1      ! iso-level not allowed
255            IF ( ln_traldf_hor   )   nldf = 2      ! horizontal (no rotation)
256            IF ( ln_traldf_iso   )   ierr = 2      ! isoneutral (   rotation)
257         ENDIF
258         IF ( ln_sco ) THEN             ! s-coordinate
259            IF ( ln_traldf_level )   nldf = 2      ! iso-level  (no rotation)
260            IF ( ln_traldf_hor   )   nldf = 3      ! horizontal (   rotation)
261            IF ( ln_traldf_iso   )   ierr = 2      ! isoneutral (   rotation)
262         ENDIF
263      ENDIF
264
265      IF( nldf == 3 )   CALL ctl_warn( 'geopotential bilaplacian tracer diffusion in s-coords not thoroughly tested' )
266      IF( ierr == 1 )   CALL ctl_stop( ' iso-level in z-coordinate - partial step, not allowed' )
267      IF( ierr == 2 )   CALL ctl_stop( ' isoneutral bilaplacian operator does not exist' )
268      IF( ln_traldf_grif .AND. ln_isfcav         )   &
269           CALL ctl_stop( ' ice shelf and traldf_grif not tested')
270      IF( lk_traldf_eiv .AND. .NOT.ln_traldf_iso )   &
271           CALL ctl_stop( '          eddy induced velocity on tracers',   &
272           &              ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion' )
273      IF( nldf == 1 .OR. nldf == 3 ) THEN      ! rotation
274         IF( .NOT.lk_ldfslp )   CALL ctl_stop( '          the rotation of the diffusive tensor require key_ldfslp' )
275         l_traldf_rot = .TRUE.                 ! needed for trazdf_imp
276      ENDIF
277
278      IF( lk_esopa ) THEN
279         IF(lwp) WRITE(numout,*) '          esopa control: use all lateral physics options'
280         IF(lwp .AND. lflush) CALL flush(numout)
281         nldf = -1
282      ENDIF
283
284      IF(lwp) THEN
285         WRITE(numout,*)
286         IF( nldf == -2 )   WRITE(numout,*) '          NO lateral diffusion'
287         IF( nldf == -1 )   WRITE(numout,*) '          ESOPA test All scheme used'
288         IF( nldf ==  0 )   WRITE(numout,*) '          laplacian operator'
289         IF( nldf ==  1 )   WRITE(numout,*) '          Rotated laplacian operator'
290         IF( nldf ==  2 )   WRITE(numout,*) '          bilaplacian operator'
291         IF( nldf ==  3 )   WRITE(numout,*) '          Rotated bilaplacian'
292         IF(lflush) CALL flush(numout)
293      ENDIF
294
295      ! Reference T & S diffusivity (if necessary)
296      ! ===========================
297      CALL ldf_ano
298      !
299   END SUBROUTINE tra_ldf_init
300
301#if defined key_traldf_ano
302   !!----------------------------------------------------------------------
303   !!   'key_traldf_ano'               T & S lateral diffusion on anomalies
304   !!----------------------------------------------------------------------
305
306   SUBROUTINE ldf_ano
307      !!----------------------------------------------------------------------
308      !!                  ***  ROUTINE ldf_ano  ***
309      !!
310      !! ** Purpose :   initializations of
311      !!----------------------------------------------------------------------
312      !
313      USE zdf_oce         ! vertical mixing
314      USE trazdf          ! vertical mixing: double diffusion
315      USE zdfddm          ! vertical mixing: double diffusion
316      !
317      INTEGER  ::   jk              ! Dummy loop indice
318      INTEGER  ::   ierr            ! local integer
319      LOGICAL  ::   llsave          ! local logical
320      REAL(wp) ::   zt0, zs0, z12   ! local scalar
321      REAL(wp), POINTER, DIMENSION(:,:,:) :: zt_ref, zs_ref, ztb, zsb, zavt     
322      !!----------------------------------------------------------------------
323      !
324      IF( nn_timing == 1 )  CALL timing_start('ldf_ano')
325      !
326      CALL wrk_alloc( jpi, jpj, jpk, zt_ref, zs_ref, ztb, zsb, zavt ) 
327      !
328
329      IF(lwp) THEN
330         WRITE(numout,*)
331         WRITE(numout,*) 'tra:ldf_ano : lateral diffusion acting on anomalies'
332         WRITE(numout,*) '~~~~~~~~~~~'
333         IF(lflush) CALL flush(numout)
334      ENDIF
335
336      !                              ! allocate trabbl arrays
337      ALLOCATE( t0_ldf(jpi,jpj,jpk) , s0_ldf(jpi,jpj,jpk) , STAT=ierr )
338      IF( lk_mpp    )   CALL mpp_sum( ierr )
339      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'ldf_ano: unable to allocate arrays' )
340
341      ! defined the T & S reference profiles
342      ! ------------------------------------
343      zt0 =10.e0                               ! homogeneous ocean
344      zs0 =35.e0
345      zt_ref(:,:,:) = 10.0 * tmask(:,:,:)
346      zs_ref(:,:,:) = 35.0 * tmask(:,:,:)
347      IF(lwp) WRITE(numout,*) '              homogeneous ocean T = ', zt0, ' S = ',zs0
348      IF(lwp .AND. lflush) CALL flush(numout)
349
350      ! Initialisation of gtui/gtvi in case of no cavity
351      IF ( .NOT. ln_isfcav ) THEN
352         gtui(:,:,:) = 0.0_wp
353         gtvi(:,:,:) = 0.0_wp
354      END IF
355      !                                        ! T & S profile (to be coded +namelist parameter
356
357      ! prepare the ldf computation
358      ! ---------------------------
359      llsave = l_trdtra
360      l_trdtra = .false.      ! desactivate trend computation
361      t0_ldf(:,:,:) = 0.e0
362      s0_ldf(:,:,:) = 0.e0
363      ztb   (:,:,:) = tsb (:,:,:,jp_tem)
364      zsb   (:,:,:) = tsb (:,:,:,jp_sal)
365      ua    (:,:,:) = tsa (:,:,:,jp_tem)
366      va    (:,:,:) = tsa (:,:,:,jp_sal)
367      zavt  (:,:,:) = avt(:,:,:)
368      IF( lk_zdfddm ) THEN CALL ctl_stop( ' key_traldf_ano with key_zdfddm not implemented' )
369      ! set tb, sb to reference values and avr to zero
370      tsb (:,:,:,jp_tem) = zt_ref(:,:,:)
371      tsb (:,:,:,jp_sal) = zs_ref(:,:,:)
372      tsa (:,:,:,jp_tem) = 0.e0
373      tsa (:,:,:,jp_sal) = 0.e0
374      avt(:,:,:)         = 0.e0
375
376      ! Compute the ldf trends
377      ! ----------------------
378      CALL tra_ldf( nit000 + 1 )      ! horizontal components (+1: no more init)
379      CALL tra_zdf( nit000     )      ! vertical component (if necessary nit000 to performed the init)
380
381      ! finalise the computation and recover all arrays
382      ! -----------------------------------------------
383      l_trdtra = llsave
384      z12 = 2.e0
385      IF( neuler == 1)   z12 = 1.e0
386      IF( ln_zdfexp ) THEN      ! ta,sa are the trends
387         t0_ldf(:,:,:) = tsa(:,:,:,jp_tem)
388         s0_ldf(:,:,:) = tsa(:,:,:,jp_sal)
389      ELSE
390         DO jk = 1, jpkm1
391            t0_ldf(:,:,jk) = ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / ( z12 *rdttra(jk) )
392            s0_ldf(:,:,jk) = ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / ( z12 *rdttra(jk) )
393         END DO
394      ENDIF
395      tsb(:,:,:,jp_tem) = ztb (:,:,:)
396      tsb(:,:,:,jp_sal) = zsb (:,:,:)
397      tsa(:,:,:,jp_tem) = ua  (:,:,:)
398      tsa(:,:,:,jp_sal) = va  (:,:,:)
399      avt(:,:,:)        = zavt(:,:,:)
400      !
401      CALL wrk_dealloc( jpi, jpj, jpk, zt_ref, zs_ref, ztb, zsb, zavt ) 
402      !
403      IF( nn_timing == 1 )  CALL timing_stop('ldf_ano')
404      !
405   END SUBROUTINE ldf_ano
406
407#else
408   !!----------------------------------------------------------------------
409   !!   default option :   Dummy code   NO T & S background profiles
410   !!----------------------------------------------------------------------
411   SUBROUTINE ldf_ano
412      IF(lwp) THEN
413         WRITE(numout,*)
414         WRITE(numout,*) 'tra:ldf_ano : lateral diffusion acting on the full fields'
415         WRITE(numout,*) '~~~~~~~~~~~'
416         IF(lflush) CALL flush(numout)
417      ENDIF
418   END SUBROUTINE ldf_ano
419#endif
420
421   !!======================================================================
422END MODULE traldf
Note: See TracBrowser for help on using the repository browser.