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.
trcldf.F90 in branches/2015/dev_r5721_CNRS9_NOC3_LDF/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2015/dev_r5721_CNRS9_NOC3_LDF/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 @ 5766

Last change on this file since 5766 was 5766, checked in by cetlod, 9 years ago

LDF: phasing the improvements/simplifications of TOP component

  • Property svn:keywords set to Id
File size: 15.3 KB
Line 
1MODULE trcldf
2   !!======================================================================
3   !!                       ***  MODULE  trcldf  ***
4   !! Ocean Passive tracers : lateral diffusive trends
5   !!=====================================================================
6   !! History :  1.0  ! 2005-11  (G. Madec)  Original code
7   !!            3.0  ! 2008-01  (C. Ethe, G. Madec)  merge TRC-TRA
8   !!            3.7  ! 2014-03  (G. Madec)  LDF simplification
9   !!----------------------------------------------------------------------
10#if defined key_top
11   !!----------------------------------------------------------------------
12   !!   'key_top'                                                TOP models
13   !!----------------------------------------------------------------------
14   !!   trc_ldf      : update the tracer trend with the lateral diffusion
15   !!   trc_ldf_ini  : initialization, namelist read, and parameters control
16   !!----------------------------------------------------------------------
17   USE trc           ! ocean passive tracers variables
18   USE oce_trc       ! ocean dynamics and active tracers
19   USE ldfslp        ! lateral diffusion: iso-neutral slope
20   USE traldf_lap    ! lateral diffusion: laplacian iso-level            operator  (tra_ldf_lap   routine)
21   USE traldf_iso    ! lateral diffusion: laplacian iso-neutral standard operator  (tra_ldf_iso   routine)
22   USE traldf_triad  ! lateral diffusion: laplacian iso-neutral triad    operator  (tra_ldf_triad routine)
23   USE traldf_blp    ! lateral diffusion (iso-level lap/blp)                       (tra_ldf_lap   routine)
24   USE trd_oce       ! trends: ocean variables
25   USE trdtra        ! trends manager: tracers
26   !
27   USE prtctl_trc      ! Print control
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   trc_ldf   
33   PUBLIC   trc_ldf_ini   
34   !
35   LOGICAL , PUBLIC ::   ln_trcldf_lap       !:   laplacian operator
36   LOGICAL , PUBLIC ::   ln_trcldf_blp       !: bilaplacian operator
37   LOGICAL , PUBLIC ::   ln_trcldf_lev       !: iso-level   direction
38   LOGICAL , PUBLIC ::   ln_trcldf_hor       !: horizontal  direction (rotation to geopotential)
39   LOGICAL , PUBLIC ::   ln_trcldf_iso       !: iso-neutral direction (standard)
40   LOGICAL , PUBLIC ::   ln_trcldf_triad     !: iso-neutral direction (triad)
41   REAL(wp), PUBLIC ::   rn_ahtrc_0          !:   laplacian diffusivity coefficient for passive tracer [m2/s]
42   REAL(wp), PUBLIC ::   rn_bhtrc_0          !: bilaplacian      -          --     -       -   [m4/s]
43   !
44                                                 !!: ** lateral mixing namelist (nam_trcldf) **
45   REAL(wp) ::  rldf    ! ratio between active and passive tracers diffusive coefficient
46   INTEGER  ::  nldf = 0   ! type of lateral diffusion used defined from ln_trcldf_... namlist logicals)
47   
48   !! * Substitutions
49#  include "domzgr_substitute.h90"
50#  include "vectopt_loop_substitute.h90"
51   !!----------------------------------------------------------------------
52   !! NEMO/TOP 3.7 , NEMO Consortium (2014)
53   !! $Id$
54   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56CONTAINS
57
58   SUBROUTINE trc_ldf( kt )
59      !!----------------------------------------------------------------------
60      !!                  ***  ROUTINE tra_ldf  ***
61      !!
62      !! ** Purpose :   compute the lateral ocean tracer physics.
63      !!
64      !!----------------------------------------------------------------------
65      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
66      !!
67      INTEGER            :: jn
68      CHARACTER (len=22) :: charout
69      REAL(wp), POINTER, DIMENSION(:,:,:)   ::   zahu, zahv
70      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd
71      !!----------------------------------------------------------------------
72      !
73      IF( nn_timing == 1 )   CALL timing_start('trc_ldf')
74      !
75     
76      IF( l_trdtrc )  THEN
77         CALL wrk_alloc( jpi,jpj,jpk,jptra,   ztrtrd )
78         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
79      ENDIF
80
81      !                                        ! set the lateral diffusivity coef. for passive tracer     
82      CALL wrk_alloc( jpi,jpj,jpk,   zahu, zahv )
83      zahu(:,:,:) = rldf * ahtu(:,:,:)
84      zahv(:,:,:) = rldf * ahtv(:,:,:)
85
86      SELECT CASE ( nldf )                     !* compute lateral mixing trend and add it to the general trend
87      !
88      CASE ( n_lap   )                                ! iso-level laplacian
89         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,  1   )
90         !
91      CASE ( n_lap_i )                                ! laplacian : standard iso-neutral operator (Madec)
92         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   )
93         !
94      CASE ( n_lap_it )                               ! laplacian : triad iso-neutral operator (griffies)
95         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,  1   )
96         !
97      CASE ( n_blp , n_blp_i , n_blp_it )             ! bilaplacian: all operator (iso-level, -neutral)
98         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf )
99         !
100      END SELECT
101      !
102      IF( l_trdtrc )   THEN                    ! save the horizontal diffusive trends for further diagnostics
103        DO jn = 1, jptra
104           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn)
105           CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
106        END DO
107        CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrtrd )
108      ENDIF
109      !                                        ! print mean trends (used for debugging)
110      IF( ln_ctl ) THEN
111         WRITE(charout, FMT="('ldf ')")   ;   CALL prt_ctl_trc_info(charout)
112                                              CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
113      ENDIF
114      !
115      CALL wrk_dealloc( jpi,jpj,jpk,   zahu, zahv )
116      !
117      IF( nn_timing == 1 )   CALL timing_stop('trc_ldf')
118      !
119   END SUBROUTINE trc_ldf
120
121!!gm ldf_ctl should be called in trcini  so that l_ldfslp=T  cause the slope init and calculation
122
123   SUBROUTINE trc_ldf_ini
124      !!----------------------------------------------------------------------
125      !!                  ***  ROUTINE ldf_ctl  ***
126      !!
127      !! ** Purpose :   Define the operator for the lateral diffusion
128      !!
129      !! ** Method  :   set nldf from the namtra_ldf logicals
130      !!      nldf == -2   No lateral diffusion
131      !!      nldf ==  0   laplacian operator
132      !!      nldf ==  1   Rotated laplacian operator
133      !!      nldf ==  2   bilaplacian operator
134      !!      nldf ==  3   Rotated bilaplacian
135      !!----------------------------------------------------------------------
136      INTEGER ::   ioptio, ierr         ! temporary integers
137      INTEGER ::  ios                 ! Local integer output status for namelist read
138      !
139      NAMELIST/namtrc_ldf/ ln_trcldf_lap, ln_trcldf_blp, &
140         &                 ln_trcldf_lev, ln_trcldf_hor, ln_trcldf_iso, ln_trcldf_triad,  &
141         &                 rn_ahtrc_0   , rn_bhtrc_0
142      !!----------------------------------------------------------------------
143      REWIND( numnat_ref )              !  namtrc_ldf in reference namelist
144      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
145903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
146
147      REWIND( numnat_cfg )              !  namtrc_ldf in configuration namelist
148      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
149904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
150      IF(lwm) WRITE ( numont, namtrc_ldf )
151
152      IF(lwp) THEN                    ! Namelist print
153         WRITE(numout,*)
154         WRITE(numout,*) 'trc_ldf_ini : lateral tracer diffusive operator'
155         WRITE(numout,*) '~~~~~~~~~~~'
156         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
157         WRITE(numout,*) '      operator'
158         WRITE(numout,*) '           laplacian                 ln_trcldf_lap   = ', ln_trcldf_lap
159         WRITE(numout,*) '         bilaplacian                 ln_trcldf_blp   = ', ln_trcldf_blp
160         WRITE(numout,*) '      direction of action'
161         WRITE(numout,*) '         iso-level                   ln_trcldf_lev   = ', ln_trcldf_lev
162         WRITE(numout,*) '         horizontal (geopotential)   ln_trcldf_hor   = ', ln_trcldf_hor
163         WRITE(numout,*) '         iso-neutral (standard)      ln_trcldf_iso   = ', ln_trcldf_iso
164         WRITE(numout,*) '         iso-neutral (triad)         ln_trcldf_triad = ', ln_trcldf_triad
165         WRITE(numout,*) '      diffusivity coefficient'
166         WRITE(numout,*) '           laplacian                 rn_ahtrc_0      = ', rn_ahtrc_0
167         WRITE(numout,*) '         bilaplacian                 rn_bhtrc_0      = ', rn_bhtrc_0
168      ENDIF
169      !     
170      !                                ! control the namelist parameters
171      ioptio = 0
172      IF( ln_trcldf_lap )   ioptio = ioptio + 1
173      IF( ln_trcldf_blp )   ioptio = ioptio + 1
174      IF( ioptio >  1 )   CALL ctl_stop( 'trc_ldf_ctl: use ONE or NONE of the 2 lap/bilap operator type on tracer' )
175      IF( ioptio == 0 )   nldf = n_no_ldf   ! No lateral diffusion
176     
177      IF( ln_trcldf_lap .AND. ln_trcldf_blp )   CALL ctl_stop( 'trc_ldf_ctl: bilaplacian should be used on both TRC and TRA' )
178      IF( ln_trcldf_blp .AND. ln_trcldf_lap )   CALL ctl_stop( 'trc_ldf_ctl:   laplacian should be used on both TRC and TRA' )
179     
180      ioptio = 0
181      IF( ln_trcldf_lev )   ioptio = ioptio + 1
182      IF( ln_trcldf_hor )   ioptio = ioptio + 1
183      IF( ln_trcldf_iso )   ioptio = ioptio + 1
184      IF( ioptio /= 1   )   CALL ctl_stop( 'trc_ldf_ctl: use only ONE direction (level/hor/iso)' )
185
186      ! defined the type of lateral diffusion from ln_trcldf_... logicals
187      ! CAUTION : nldf = 1 is used in trazdf_imp, change it carefully
188      ierr = 0
189      IF( ln_trcldf_lap ) THEN      !==  laplacian operator  ==!
190         IF ( ln_zco ) THEN                ! z-coordinate
191            IF ( ln_trcldf_lev   )   nldf = n_lap     ! iso-level = horizontal (no rotation)
192            IF ( ln_trcldf_hor   )   nldf = n_lap     ! iso-level = horizontal (no rotation)
193            IF ( ln_trcldf_iso   )   nldf = n_lap_i   ! iso-neutral: standard  (   rotation)
194            IF ( ln_trcldf_triad )   nldf = n_lap_it  ! iso-neutral: triad     (   rotation)
195         ENDIF
196         IF ( ln_zps ) THEN             ! z-coordinate with partial step
197            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed
198            IF ( ln_trcldf_hor   )   nldf = n_lap     ! horizontal (no rotation)
199            IF ( ln_trcldf_iso   )   nldf = n_lap_i   ! iso-neutral: standard (rotation)
200            IF ( ln_trcldf_triad )   nldf = n_lap_it  ! iso-neutral: triad    (rotation)
201         ENDIF
202         IF ( ln_sco ) THEN             ! s-coordinate
203            IF ( ln_trcldf_lev   )   nldf = n_lap     ! iso-level  (no rotation)
204            IF ( ln_trcldf_hor   )   nldf = n_lap_it  ! horizontal (   rotation)       !!gm   a checker....
205            IF ( ln_trcldf_iso   )   nldf = n_lap_i   ! iso-neutral: standard (rotation)
206            IF ( ln_trcldf_triad )   nldf = n_lap_it  ! iso-neutral: triad    (rotation)
207         ENDIF
208         !                                ! diffusivity ratio: passive / active tracers
209         IF( ABS(rn_aht_0) < 2._wp*TINY(1.e0) ) THEN
210            IF( ABS(rn_ahtrc_0) < 2._wp*TINY(1.e0) ) THEN
211               rldf = 1.0_wp
212            ELSE
213               CALL ctl_stop( 'STOP', 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' )
214            ENDIF
215         ELSE
216            rldf = rn_ahtrc_0 / rn_aht_0
217         ENDIF
218      ENDIF
219
220      IF( ln_trcldf_blp ) THEN      !==  bilaplacian operator  ==!
221         IF ( ln_zco ) THEN                ! z-coordinate
222            IF ( ln_trcldf_lev   )   nldf = n_blp     ! iso-level = horizontal (no rotation)
223            IF ( ln_trcldf_hor   )   nldf = n_blp     ! iso-level = horizontal (no rotation)
224            IF ( ln_trcldf_iso   )   nldf = n_blp_i   ! iso-neutral: standard (rotation)
225            IF ( ln_trcldf_triad )   nldf = n_blp_it  ! iso-neutral: triad    (rotation)
226         ENDIF
227         IF ( ln_zps ) THEN             ! z-coordinate with partial step
228            IF ( ln_trcldf_lev   )   ierr = 1         ! iso-level not allowed
229            IF ( ln_trcldf_hor   )   nldf = n_blp     ! horizontal (no rotation)
230            IF ( ln_trcldf_iso   )   nldf = n_blp_i   ! iso-neutral: standard (rotation)
231            IF ( ln_trcldf_triad )   nldf = n_blp_it  ! iso-neutral: triad    (rotation)
232         ENDIF
233         IF ( ln_sco ) THEN             ! s-coordinate
234            IF ( ln_trcldf_lev   )   nldf = n_blp     ! iso-level  (no rotation)
235            IF ( ln_trcldf_hor   )   nldf = n_blp_it  ! horizontal (   rotation)       !!gm   a checker....
236            IF ( ln_trcldf_iso   )   nldf = n_blp_i   ! iso-neutral: standard (rotation)
237            IF ( ln_trcldf_triad )   nldf = n_blp_it  ! iso-neutral: triad    (rotation)
238         ENDIF
239         !                                ! diffusivity ratio: passive / active tracers
240         IF( ABS(rn_bht_0) < 2._wp*TINY(1.e0) ) THEN
241            IF( ABS(rn_bhtrc_0) < 2._wp*TINY(1.e0) ) THEN
242               rldf = 1.0_wp
243            ELSE
244               CALL ctl_stop( 'STOP', 'trc_ldf_ctl : cannot define rldf, rn_aht_0==0, rn_ahtrc_0 /=0' )
245            ENDIF
246         ELSE
247            rldf = SQRT(  ABS( rn_bhtrc_0 / rn_bht_0 )  )
248         ENDIF
249      ENDIF
250
251      IF( ierr == 1 )   CALL ctl_stop( ' iso-level in z-coordinate - partial step, not allowed' )
252      IF( ln_ldfeiv .AND. .NOT.ln_trcldf_iso )   &
253           CALL ctl_stop( '          eddy induced velocity on tracers',   &
254           &              ' the eddy induced velocity on tracers requires isopycnal laplacian diffusion' )
255      IF( nldf == 1 .OR. nldf == 3 ) THEN      ! rotation
256         IF( .NOT.l_ldfslp )   CALL ctl_stop( '          the rotation of the diffusive tensor require l_ldfslp' )
257      ENDIF
258
259      IF(lwp) THEN
260         WRITE(numout,*)
261         IF( nldf == n_no_ldf )   WRITE(numout,*) '          NO lateral diffusion'
262         IF( nldf == n_lap    )   WRITE(numout,*) '          laplacian iso-level operator'
263         IF( nldf == n_lap_i  )   WRITE(numout,*) '          Rotated laplacian operator (standard)'
264         IF( nldf == n_lap_it )   WRITE(numout,*) '          Rotated laplacian operator (triad)'
265         IF( nldf == n_blp    )   WRITE(numout,*) '          bilaplacian iso-level operator'
266         IF( nldf == n_blp_i  )   WRITE(numout,*) '          Rotated bilaplacian operator (standard)'
267         IF( nldf == n_blp_it )   WRITE(numout,*) '          Rotated bilaplacian operator (triad)'
268      ENDIF
269      !
270   END SUBROUTINE trc_ldf_ini
271#else
272   !!----------------------------------------------------------------------
273   !!   Default option                                         Empty module
274   !!----------------------------------------------------------------------
275CONTAINS
276   SUBROUTINE trc_ldf( kt )
277      INTEGER, INTENT(in) :: kt
278      WRITE(*,*) 'trc_ldf: You should not have seen this print! error?', kt
279   END SUBROUTINE trc_ldf
280#endif
281   !!======================================================================
282END MODULE trcldf
Note: See TracBrowser for help on using the repository browser.