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/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/TRP/trcldf.F90 @ 9019

Last change on this file since 9019 was 9019, checked in by timgraham, 6 years ago

Merge of dev_CNRS_2017 into branch

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