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

source: trunk/NEMOGCM/NEMO/OPA_SRC/TRA/traldf.F90 @ 3389

Last change on this file since 3389 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

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