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

Last change on this file since 197 was 186, checked in by opalod, 20 years ago

CL + CE : NEMO TRC_SRC start

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 9.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
12   USE trc                 ! ocean space and time domain
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   !! Lateral diffusion
31   LOGICAL , PUBLIC ::              & !!: ** lateral mixing namelist (nam_trcldf) **
32      ln_trcldf_diff  = .FALSE. ,   &  !: flag of perform or not the lateral diff.
33      ln_trcldf_lap   = .TRUE.  ,   &  !: laplacian operator
34      ln_trcldf_bilap = .FALSE. ,   &  !: bilaplacian operator
35      ln_trcldf_level = .FALSE. ,   &  !: iso-level direction
36      ln_trcldf_hor   = .FALSE. ,   &  !: horizontal (geopotential) direction
37      ln_trcldf_iso   = .TRUE.         !: iso-neutral direction
38
39   LOGICAL , PUBLIC ::              &  !: flag of the lateral diff. scheme used
40      l_trcldf_lap         ,        &  !: iso-level laplacian operator
41      l_trcldf_bilap       ,        &  !: iso-level bilaplacian operator
42      l_trcldf_bilapg      ,        &  !: geopotential bilap. (s-coord)
43      l_trcldf_iso         ,        &  !: iso-neutral laplacian or horizontal lapacian (s-coord)
44      l_trczdf_iso         ,        &  !: idem for the vertical component
45      l_trczdf_iso_vo      ,        &  !: idem with vectopt_memory
46      l_trcldf_iso_zps                 !: iso-neutral laplacian (partial steps)
47
48   !! Vertical diffusion
49   LOGICAL , PUBLIC ::           & !!! nam_trczdf: vertical diffusion
50      ln_trczdf_exp = .FALSE.   ! explicit vertical diffusion scheme flag
51
52   INTEGER, PUBLIC ::    & !!: namzdf:  vertical diffusion
53      n_trczdf_exp = 3          !: number of sub-time step (explicit time stepping)
54
55   LOGICAL, PUBLIC ::    &   !:
56      l_trczdf_exp     = .FALSE. ,   &  !: ???
57      l_trczdf_imp     = .FALSE.         !:
58
59#if defined key_trcdmp
60   !! Newtonian damping
61   INTEGER  , PUBLIC ::             & !!! * newtonian damping namelist (nam_trcdmp) *
62      ndmptr   =   -1 ,      &  ! = 0/-1/'latitude' for damping over tracers
63      ndmpftr  =    2 ,      &  ! = 1 create a damping.coeff NetCDF file
64      nmldmptr =    0           ! = 0/1/2 flag for damping in the mixed layer
65
66   REAL(wp) , PUBLIC ::             & !!!  * newtonian damping namelist *
67      sdmptr   =   50.,      &  ! surface time scale for internal damping (days)
68      bdmptr   =  360.,      &  ! bottom time scale for internal damping (days)
69      hdmptr   =  800.          ! depth of transition between sdmp and bdmp (meters)
70#endif
71   !!----------------------------------------------------------------------
72   !!   OPA 9.0 , LODYC-IPSL (2003)
73   !!----------------------------------------------------------------------
74
75CONTAINS
76
77   SUBROUTINE trc_trp_lec
78      !!---------------------------------------------------------------------
79      !!                  ***  ROUTINE trc_trp_lec  ***
80      !!               
81      !! ** Purpose :   Read Namelist for tracer transport option
82      !!
83      !! History :
84      !!
85      !!   9.0  !  04-03  (C. Ethe)
86      !!----------------------------------------------------------------------
87      !! * Local declarations
88
89      NAMELIST/namtrcadv/ ln_trcadv_cen2 , ln_trcadv_tvd,   &
90         &                 ln_trcadv_muscl, ln_trcadv_muscl2, ln_trcadv_smolar
91
92      NAMELIST/namtrcldf/  ln_trcldf_diff  , ln_trcldf_lap  , ln_trcldf_bilap, &
93         &                 ln_trcldf_level, ln_trcldf_hor, ln_trcldf_iso,   &
94         &                 ahtrc0, ahtrb0, aeivtr0, trcrat
95
96      NAMELIST/namtrczdf/ ln_trczdf_exp, n_trczdf_exp
97
98#if defined key_trcdmp
99      NAMELIST/namtrcdmp/ ndmptr, ndmpftr, nmldmptr, sdmptr, bdmptr, hdmptr
100#endif
101      !!----------------------------------------------------------------------
102
103      ! Read Namelist namtrcadv : tracer advection scheme
104      ! -------------------------
105      REWIND ( numnat )
106      READ   ( numnat, namtrcadv )
107
108      ! Parameter control and print
109      ! ---------------------------
110      ! Control print
111      IF(lwp) THEN
112         WRITE(numout,*)
113         WRITE(numout,*) 'choice/control of the tracer advection scheme'
114         WRITE(numout,*) '~~~~~~~~~~~'
115         WRITE(numout,*) '          Namelist namtrcadv : chose a advection scheme for tracers'
116         WRITE(numout,*)
117         WRITE(numout,*) '             2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
118         WRITE(numout,*) '             TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
119         WRITE(numout,*) '             MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
120         WRITE(numout,*) '             MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
121         WRITE(numout,*) '             SMOLARKIEWICZ advection scheme ln_trcadv_smolar = ', ln_trcadv_smolar
122      ENDIF
123
124      !  Define the lateral tracer physics parameters
125      ! =============================================
126   
127      ! Read Namelist namtrcldf : Lateral physics on tracers
128      REWIND( numnat )
129      READ  ( numnat, namtrcldf )
130
131      IF(lwp) THEN
132         WRITE(numout,*)
133         WRITE(numout,*) 'lateral passive tracer physics'
134         WRITE(numout,*) '~~~~~~~'
135         WRITE(numout,*) '   Namelist namtrcldf : set lateral mixing parameters (type, direction, coefficients)'
136         WRITE(numout,*) '     perform lateral diffusion or not               ln_trcldf_diff  = ', ln_trcldf_diff
137         WRITE(numout,*) '     laplacian operator                             ln_trcldf_lap   = ', ln_trcldf_lap
138         WRITE(numout,*) '     bilaplacian operator                           ln_trcldf_bilap = ', ln_trcldf_bilap
139         WRITE(numout,*) '     iso-level                                      ln_trcldf_level = ', ln_trcldf_level
140         WRITE(numout,*) '     horizontal (geopotential)                      ln_trcldf_hor   = ', ln_trcldf_hor
141         WRITE(numout,*) '     iso-neutral                                    ln_trcldf_iso   = ', ln_trcldf_iso
142         WRITE(numout,*) '     lateral eddy diffusivity                              ahtrc0   = ', ahtrc0
143         WRITE(numout,*) '     background hor. diffusivity                            ahtrb0  = ', ahtrb0
144         WRITE(numout,*) '     eddy induced velocity coef.                           aeivtr0  = ', aeivtr0
145         WRITE(numout,*) '     ratio between passive and active tracer diffusion coef  trcrat = ', trcrat
146      ENDIF
147
148      ! Read namtrczdf namelist : vertical mixing parameters
149      ! --------------------
150      REWIND( numnat )
151      READ  ( numnat, namtrczdf )
152
153      ! Parameter print
154      ! ---------------
155      IF(lwp) THEN
156         WRITE(numout,*)
157         WRITE(numout,*) 'vertical physics'
158         WRITE(numout,*) '~~~~~~~~'
159         WRITE(numout,*) '          Namelist namtrczdf : set vertical diffusion parameters'
160         WRITE(numout,*) '             time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
161         WRITE(numout,*) '             number of time step               n_trczdf_exp = ', n_trczdf_exp
162      ENDIF
163
164# if defined key_trcdmp
165      ! Read Namelist namtdp : passive tracres damping term
166      ! --------------------
167      REWIND ( numnat )
168      READ   ( numnat, namtrcdmp )
169      IF( lzoom ) THEN
170         nmldmptr = 0           ! restoring to climatology at closed north or south boundaries
171      ENDIF
172
173      ! Parameter control and print
174      ! ---------------------------
175      IF(lwp) THEN
176         WRITE(numout,*)
177         WRITE(numout,*) 'newtonian damping'
178         WRITE(numout,*) '~~~~~~~'
179         WRITE(numout,*) '          Namelist namtrcdmp : set damping parameter'
180         WRITE(numout,*)
181         WRITE(numout,*) '             tracers damping option         ndmptr   = ', ndmptr
182         WRITE(numout,*) '             create a damping.coeff file    ndmpftr  = ', ndmpftr
183         WRITE(numout,*) '             mixed layer damping option     nmldmptr = ', nmldmptr, '(zoom: forced to 0)'
184         WRITE(numout,*) '             surface time scale (days)      sdmptr   = ', sdmptr
185         WRITE(numout,*) '             bottom time scale (days)       bdmptr   = ', bdmptr
186         WRITE(numout,*) '             depth of transition (meters)   hdmptr   = ', hdmptr
187         WRITE(numout,*)
188      ENDIF
189
190#endif
191
192   END SUBROUTINE trc_trp_lec
193#else
194   !!----------------------------------------------------------------------
195   !!   Dummy module :                      Rigid-lid case
196   !!----------------------------------------------------------------------
197CONTAINS
198   SUBROUTINE trc_trp_lec              ! Empty routine
199   END SUBROUTINE trc_trp_lec
200#endif
201  !!======================================================================
202END MODULE trctrp_lec
Note: See TracBrowser for help on using the repository browser.