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 @ 5758

Last change on this file since 5758 was 5758, checked in by gm, 9 years ago

#1593: LDF-ADV, step II.1: phasing the improvements/simplifications of diffusive trend (see wiki)

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