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.
trctrp_lec.F90 in trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trctrp_lec.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 10.5 KB
Line 
1MODULE trctrp_lec
2   !!==============================================================================
3   !!                       ***  MODULE  trctrp_lec  ***
4   !! Ocean passive tracers:  namelist read options for transport
5   !!==============================================================================
6#if defined key_passivetrc
7   !!----------------------------------------------------------------------
8   !!   trc_trp_lec  : read the passive tracer namelist for transport
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce_trc             ! ocean dynamics and active tracers variables
12   USE trc                 ! ocean passive tracers variables
13
14   IMPLICIT NONE
15   PRIVATE
16
17   !! * Accessibility
18   PUBLIC trc_trp_lec     ! routine called by step module
19 
20   !! * Share module variables
21
22   !! Advection
23   LOGICAL, PUBLIC ::   &
24      ln_trcadv_cen2   = .FALSE. ,  & !!: 2nd order centered scheme flag
25      ln_trcadv_tvd    = .FALSE. ,  &  !: TVD scheme flag
26      ln_trcadv_muscl  = .FALSE. ,  &  !: MUSCL scheme flag
27      ln_trcadv_muscl2 = .FALSE. ,  &  !: MUSCL2 scheme flag
28      ln_trcadv_smolar = .TRUE.        !: Smolarkiewicz scheme flag
29
30   !! Bottom boundary layer
31   REAL(wp), PUBLIC ::        & 
32      atrcbbl = 1.e+3      ! lateral coeff. for bottom boundary layer scheme (m2/s)
33
34   !! Lateral diffusion
35   LOGICAL , PUBLIC ::              & !!: ** lateral mixing namelist (nam_trcldf) **
36      ln_trcldf_diff  = .FALSE. ,   &  !: flag of perform or not the lateral diff.
37      ln_trcldf_lap   = .TRUE.  ,   &  !: laplacian operator
38      ln_trcldf_bilap = .FALSE. ,   &  !: bilaplacian operator
39      ln_trcldf_level = .FALSE. ,   &  !: iso-level direction
40      ln_trcldf_hor   = .FALSE. ,   &  !: horizontal (geopotential) direction
41      ln_trcldf_iso   = .TRUE.         !: iso-neutral direction
42
43   LOGICAL , PUBLIC ::              & !!: flag of the lateral diff. scheme used
44      l_trcldf_lap         ,        &  !: iso-level laplacian operator
45      l_trcldf_bilap       ,        &  !: iso-level bilaplacian operator
46      l_trcldf_bilapg      ,        &  !: geopotential bilap. (s-coord)
47      l_trcldf_iso         ,        &  !: iso-neutral laplacian or horizontal lapacian (s-coord)
48      l_trczdf_iso         ,        &  !: idem for the vertical component
49      l_trczdf_iso_vo      ,        &  !: idem with vectopt_memory
50      l_trcldf_iso_zps                 !: iso-neutral laplacian (partial steps)
51
52   !! Vertical diffusion
53   LOGICAL , PUBLIC ::              & !!: nam_trczdf: vertical diffusion
54      ln_trczdf_exp = .FALSE.          !: explicit vertical diffusion scheme flag
55
56   INTEGER, PUBLIC ::               & !!: namzdf:  vertical diffusion
57      n_trczdf_exp = 3                 !: number of sub-time step (explicit time stepping)
58
59   LOGICAL, PUBLIC ::               &  !:
60      l_trczdf_exp     = .FALSE. ,  &  !: explicit vertical diffusion
61      l_trczdf_imp     = .FALSE.       !: implicit vertical diffusion
62
63#if defined key_trcdmp
64   !! Newtonian damping
65   INTEGER  , PUBLIC ::             & !!: * newtonian damping namelist (nam_trcdmp) *
66      ndmptr   =   -1 ,             &  !: = 0/-1/'latitude' for damping over tracers
67      ndmpftr  =    2 ,             &  !: = 1 create a damping.coeff NetCDF file
68      nmldmptr =    0                  !: = 0/1/2 flag for damping in the mixed layer
69
70   REAL(wp) , PUBLIC ::             & !!:  * newtonian damping namelist *
71      sdmptr   =   50.,             &  !: surface time scale for internal damping (days)
72      bdmptr   =  360.,             &  !: bottom time scale for internal damping (days)
73      hdmptr   =  800.                 !: depth of transition between sdmp and bdmp (meters)
74#endif
75   !!----------------------------------------------------------------------
76   !!   TOP 1.0 , LOCEAN-IPSL (2005)
77   !! $Header$
78   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
79   !!----------------------------------------------------------------------
80
81CONTAINS
82
83   SUBROUTINE trc_trp_lec
84      !!---------------------------------------------------------------------
85      !!                  ***  ROUTINE trc_trp_lec  ***
86      !!               
87      !! ** Purpose :   Read Namelist for tracer transport option
88      !!
89      !! History :
90      !!   9.0  !  04-03  (C. Ethe)
91      !!----------------------------------------------------------------------
92      !! * Local declarations
93
94      NAMELIST/namtrcadv/ ln_trcadv_cen2 , ln_trcadv_tvd,   &
95         &                 ln_trcadv_muscl, ln_trcadv_muscl2, ln_trcadv_smolar
96
97#if  defined key_trcbbl_dif   ||   defined key_trcbbl_adv 
98      NAMELIST/namtrcbbl/ atrcbbl
99#endif
100
101      NAMELIST/namtrcldf/  ln_trcldf_diff  , ln_trcldf_lap  , ln_trcldf_bilap, &
102         &                 ln_trcldf_level, ln_trcldf_hor, ln_trcldf_iso,   &
103         &                 ahtrc0, ahtrb0, aeivtr0, trcrat
104
105      NAMELIST/namtrczdf/ ln_trczdf_exp, n_trczdf_exp
106
107#if defined key_trcdmp
108      NAMELIST/namtrcdmp/ ndmptr, ndmpftr, nmldmptr, sdmptr, bdmptr, hdmptr
109#endif
110      !!----------------------------------------------------------------------
111
112      ! Read Namelist namtrcadv : tracer advection scheme
113      ! -------------------------
114      REWIND ( numnat )
115      READ   ( numnat, namtrcadv )
116
117      ! Parameter control and print
118      ! ---------------------------
119      ! Control print
120      IF(lwp) THEN
121         WRITE(numout,*)
122         WRITE(numout,*) 'choice/control of the tracer advection scheme'
123         WRITE(numout,*) '~~~~~~~~~~~'
124         WRITE(numout,*) '          Namelist namtrcadv : chose a advection scheme for tracers'
125         WRITE(numout,*)
126         WRITE(numout,*) '             2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
127         WRITE(numout,*) '             TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
128         WRITE(numout,*) '             MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
129         WRITE(numout,*) '             MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
130         WRITE(numout,*) '             SMOLARKIEWICZ advection scheme ln_trcadv_smolar = ', ln_trcadv_smolar
131      ENDIF
132
133#if  defined key_trcbbl_dif
134      ! Read Namelist namtrcbbl : Bottom boundary layer coef
135      ! --------------------------------------------------
136      REWIND ( numnat )
137      READ   ( numnat, namtrcbbl )
138
139      ! Parameter control and print
140      ! ---------------------------
141      IF(lwp) THEN
142         WRITE(numout,*) ' Diffusive Bottom Boundary Layer'
143         WRITE(numout,*) '~~~~~~~~'
144         WRITE(numout,*) ' bottom boundary layer coef.    atrcbbl = ', atrcbbl
145# if defined key_trcbbl_adv
146            WRITE(numout,*) ' * Advective Bottom Boundary Layer'
147# endif
148         WRITE(numout,*)
149      ENDIF
150#endif
151
152      !  Define the lateral tracer physics parameters
153      ! =============================================
154   
155      ! Read Namelist namtrcldf : Lateral physics on tracers
156      REWIND( numnat )
157      READ  ( numnat, namtrcldf )
158
159      IF(lwp) THEN
160         WRITE(numout,*)
161         WRITE(numout,*) 'lateral passive tracer physics'
162         WRITE(numout,*) '~~~~~~~'
163         WRITE(numout,*) '   Namelist namtrcldf : set lateral mixing parameters (type, direction, coefficients)'
164         WRITE(numout,*) '     perform lateral diffusion or not               ln_trcldf_diff  = ', ln_trcldf_diff
165         WRITE(numout,*) '     laplacian operator                             ln_trcldf_lap   = ', ln_trcldf_lap
166         WRITE(numout,*) '     bilaplacian operator                           ln_trcldf_bilap = ', ln_trcldf_bilap
167         WRITE(numout,*) '     iso-level                                      ln_trcldf_level = ', ln_trcldf_level
168         WRITE(numout,*) '     horizontal (geopotential)                      ln_trcldf_hor   = ', ln_trcldf_hor
169         WRITE(numout,*) '     iso-neutral                                    ln_trcldf_iso   = ', ln_trcldf_iso
170         WRITE(numout,*) '     lateral eddy diffusivity                              ahtrc0   = ', ahtrc0
171         WRITE(numout,*) '     background hor. diffusivity                            ahtrb0  = ', ahtrb0
172         WRITE(numout,*) '     eddy induced velocity coef.                           aeivtr0  = ', aeivtr0
173         WRITE(numout,*) '     ratio between passive and active tracer diffusion coef  trcrat = ', trcrat
174      ENDIF
175
176      ! Read namtrczdf namelist : vertical mixing parameters
177      ! --------------------
178      REWIND( numnat )
179      READ  ( numnat, namtrczdf )
180
181      ! Parameter print
182      ! ---------------
183      IF(lwp) THEN
184         WRITE(numout,*)
185         WRITE(numout,*) 'vertical physics'
186         WRITE(numout,*) '~~~~~~~~'
187         WRITE(numout,*) '          Namelist namtrczdf : set vertical diffusion parameters'
188         WRITE(numout,*) '             time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
189         WRITE(numout,*) '             number of time step               n_trczdf_exp = ', n_trczdf_exp
190      ENDIF
191
192# if defined key_trcdmp
193      ! Read Namelist namtdp : passive tracres damping term
194      ! --------------------
195      REWIND ( numnat )
196      READ   ( numnat, namtrcdmp )
197      IF( lzoom ) THEN
198         nmldmptr = 0           ! restoring to climatology at closed north or south boundaries
199      ENDIF
200
201      ! Parameter control and print
202      ! ---------------------------
203      IF(lwp) THEN
204         WRITE(numout,*)
205         WRITE(numout,*) 'newtonian damping'
206         WRITE(numout,*) '~~~~~~~'
207         WRITE(numout,*) '          Namelist namtrcdmp : set damping parameter'
208         WRITE(numout,*)
209         WRITE(numout,*) '             tracers damping option         ndmptr   = ', ndmptr
210         WRITE(numout,*) '             create a damping.coeff file    ndmpftr  = ', ndmpftr
211         WRITE(numout,*) '             mixed layer damping option     nmldmptr = ', nmldmptr, '(zoom: forced to 0)'
212         WRITE(numout,*) '             surface time scale (days)      sdmptr   = ', sdmptr
213         WRITE(numout,*) '             bottom time scale (days)       bdmptr   = ', bdmptr
214         WRITE(numout,*) '             depth of transition (meters)   hdmptr   = ', hdmptr
215         WRITE(numout,*)
216      ENDIF
217
218#endif
219
220   END SUBROUTINE trc_trp_lec
221#else
222   !!----------------------------------------------------------------------
223   !!   Dummy module :                      NO passive tracer
224   !!----------------------------------------------------------------------
225CONTAINS
226   SUBROUTINE trc_trp_lec              ! Empty routine
227   END SUBROUTINE trc_trp_lec
228#endif
229  !!======================================================================
230END MODULE trctrp_lec
Note: See TracBrowser for help on using the repository browser.