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 NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/TRP – NEMO

source: NEMO/branches/2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles/src/TOP/TRP/trcldf.F90 @ 11671

Last change on this file since 11671 was 11671, checked in by acc, 5 years ago

Branch 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. Final, non-substantive changes to complete this branch. These changes remove all REWIND statements on the old namelist fortran units (now character variables for internal files). These changes have been left until last since they are easily repeated via a script and it may be preferable to use the previous revision for merge purposes and reapply these last changes separately. This branch has been fully SETTE tested.

  • Property svn:keywords set to Id
File size: 9.9 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 ldftra         ! lateral diffusion: eddy diffusivity & EIV coeff.
20   USE ldfslp         ! Lateral diffusion: slopes of neutral surfaces
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
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   !                                      !!: ** lateral mixing namelist (nam_trcldf) **
36   LOGICAL , PUBLIC ::   ln_trcldf_OFF     !: No operator (no explicit lateral diffusion)
37   LOGICAL , PUBLIC ::   ln_trcldf_tra     !: use active tracer operator
38   REAL(wp), PUBLIC ::      rn_ldf_multi      !: multiplier of T-S eddy diffusivity to obtain the passive tracer one
39   REAL(wp), PUBLIC ::      rn_fact_lap       !: enhanced Equatorial zonal diffusivity coefficent
40   !
41   INTEGER  ::   nldf_trc = 0   ! type of lateral diffusion used defined from ln_traldf_... (namlist logicals)
42   REAL(wp) ::   rldf           ! multiplier between active and passive tracers eddy diffusivity   [-]
43   
44   !! * Substitutions
45#  include "vectopt_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
48   !! $Id$
49   !! Software governed by the CeCILL license (see ./LICENSE)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE trc_ldf( kt )
54      !!----------------------------------------------------------------------
55      !!                  ***  ROUTINE tra_ldf  ***
56      !!
57      !! ** Purpose :   compute the lateral ocean tracer physics.
58      !!
59      !!----------------------------------------------------------------------
60      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
61      !
62      INTEGER            :: ji, jj, jk, jn
63      REAL(wp)           :: zdep
64      CHARACTER (len=22) :: charout
65      REAL(wp), DIMENSION(jpi,jpj,jpk)   ::   zahu, zahv
66      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::   ztrtrd
67      !!----------------------------------------------------------------------
68      !
69      IF( ln_trcldf_OFF )   RETURN        ! not lateral diffusion applied on passive tracers
70      !
71      IF( ln_timing )   CALL timing_start('trc_ldf')
72      !
73      IF( l_trdtrc )  THEN
74         ALLOCATE( ztrtrd(jpi,jpj,jpk,jptra) )
75         ztrtrd(:,:,:,:)  = tra(:,:,:,:)
76      ENDIF
77      !                                  !* set the lateral diffusivity coef. for passive tracer     
78      zahu(:,:,:) = rldf * ahtu(:,:,:) 
79      zahv(:,:,:) = rldf * ahtv(:,:,:)
80      !                                  !* Enhanced zonal diffusivity coefficent in the equatorial domain
81      DO jk= 1, jpk
82         DO jj = 1, jpj
83            DO ji = 1, jpi
84               IF( gdept_n(ji,jj,jk) > 200. .AND. gphit(ji,jj) < 5. .AND. gphit(ji,jj) > -5. ) THEN
85                  zdep = MAX( gdept_n(ji,jj,jk) - 1000., 0. ) / 1000.
86                  zahu(ji,jj,jk) = zahu(ji,jj,jk) * MAX( 1., rn_fact_lap * EXP( -zdep ) )
87               ENDIF
88            END DO
89         END DO
90      END DO
91      !
92      SELECT CASE ( nldf_trc )                 !* compute lateral mixing trend and add it to the general trend
93      !
94      CASE ( np_lap   )                               ! iso-level laplacian
95         CALL tra_ldf_lap  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb,      tra, jptra,    1     )
96      CASE ( np_lap_i )                               ! laplacian : standard iso-neutral operator (Madec)
97         CALL tra_ldf_iso  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,    1     )
98      CASE ( np_lap_it )                              ! laplacian : triad iso-neutral operator (griffies)
99         CALL tra_ldf_triad( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb, trb, tra, jptra,    1     )
100      CASE ( np_blp , np_blp_i , np_blp_it )          ! bilaplacian: all operator (iso-level, -neutral)
101         CALL tra_ldf_blp  ( kt, nittrc000,'TRC', zahu, zahv, gtru, gtrv, gtrui, gtrvi, trb     , tra, jptra, nldf_trc )
102      END SELECT
103      !
104      IF( l_trdtrc )   THEN                    ! send the trends for further diagnostics
105        DO jn = 1, jptra
106           ztrtrd(:,:,:,jn) = tra(:,:,:,jn) - ztrtrd(:,:,:,jn)
107           CALL trd_tra( kt, 'TRC', jn, jptra_ldf, ztrtrd(:,:,:,jn) )
108        END DO
109        DEALLOCATE( ztrtrd )
110      ENDIF
111      !               
112      IF( ln_ctl ) THEN                        ! print mean trends (used for debugging)
113         WRITE(charout, FMT="('ldf ')")
114         CALL prt_ctl_trc_info(charout)
115         CALL prt_ctl_trc( tab4d=tra, mask=tmask, clinfo=ctrcnm, clinfo2='trd' )
116      ENDIF
117      !
118      IF( ln_timing )   CALL timing_stop('trc_ldf')
119      !
120   END SUBROUTINE trc_ldf
121
122
123   SUBROUTINE trc_ldf_ini
124      !!----------------------------------------------------------------------
125      !!                  ***  ROUTINE ldf_ctl  ***
126      !!
127      !! ** Purpose :   Define the operator for the lateral diffusion
128      !!
129      !! ** Method  : - ln_trcldf_tra=T : use nldf_tra set in ldftra module
130      !!              to defined the passive tracer lateral diffusive operator
131      !!              - ln_trcldf_OFF=T : no explicit diffusion used
132      !!----------------------------------------------------------------------
133      INTEGER ::   ios, ioptio   ! local integers
134      !!
135      NAMELIST/namtrc_ldf/ ln_trcldf_OFF , ln_trcldf_tra,   &   ! operator & direction
136         &                 rn_ldf_multi  , rn_fact_lap          ! coefficient
137      !!----------------------------------------------------------------------
138      !
139      IF(lwp) THEN
140         WRITE(numout,*)
141         WRITE(numout,*) 'trc_ldf_ini : lateral passive tracer diffusive operator'
142         WRITE(numout,*) '~~~~~~~~~~~'
143      ENDIF
144      !
145      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
146903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist' )
147      !
148      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
149904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist' )
150      IF(lwm) WRITE ( numont, namtrc_ldf )
151      !
152      IF(lwp) THEN                     ! Namelist print
153         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
154         WRITE(numout,*) '      no explicit diffusion                 ln_trcldf_OFF   = ', ln_trcldf_OFF
155         WRITE(numout,*) '      use active tracer operator            ln_trcldf_tra   = ', ln_trcldf_tra
156         WRITE(numout,*) '      diffusivity coefficient :'
157         WRITE(numout,*) '         multiplier of TRA coef. for TRC       rn_ldf_multi = ', rn_ldf_multi
158         WRITE(numout,*) '         enhanced zonal Eq. laplacian coef.    rn_fact_lap  = ', rn_fact_lap
159
160      ENDIF
161      !     
162      !                                ! control the namelist parameters
163      nldf_trc = np_ERROR
164      ioptio   = 0
165      IF( ln_trcldf_OFF  ) THEN   ;   nldf_trc = np_no_ldf   ;   ioptio = ioptio + 1   ;   ENDIF
166      IF( ln_trcldf_tra  ) THEN   ;   nldf_trc = nldf_tra    ;   ioptio = ioptio + 1   ;   ENDIF
167      IF( ioptio /=  1   )   CALL ctl_stop( 'trc_ldf_ini: use ONE of the 2 operator options (NONE/tra)' )
168     
169      !                                ! multiplier : passive/active tracers ration
170      IF( ln_traldf_lap ) THEN               ! laplacian operator
171         rldf = rn_ldf_multi                       ! simple multiplier
172      ELSEIF( ln_traldf_blp ) THEN           ! bilaplacian operator:
173         rldf = SQRT( ABS( rn_ldf_multi )  )       ! the coef. used is the SQRT of the bilaplacian coef.
174      ENDIF
175      !
176      IF(lwp) THEN
177         WRITE(numout,*)
178         SELECT CASE( nldf_trc )
179         CASE( np_no_ldf )   ;   WRITE(numout,*) '      ===>>   NO lateral diffusion'
180         CASE( np_lap    )   ;   WRITE(numout,*) '      ===>>   laplacian iso-level operator'
181         CASE( np_lap_i  )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (standard)'
182         CASE( np_lap_it )   ;   WRITE(numout,*) '      ===>>   Rotated laplacian operator (triad)'
183         CASE( np_blp    )   ;   WRITE(numout,*) '      ===>>   bilaplacian iso-level operator'
184         CASE( np_blp_i  )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (standard)'
185         CASE( np_blp_it )   ;   WRITE(numout,*) '      ===>>   Rotated bilaplacian operator (triad)'
186         END SELECT
187      ENDIF
188      !
189   END SUBROUTINE trc_ldf_ini
190
191#endif
192   !!======================================================================
193END MODULE trcldf
Note: See TracBrowser for help on using the repository browser.