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

Last change on this file since 1119 was 1119, checked in by cetlod, 16 years ago

style of all top namelist has been modified ; update modules to take it into account, see ticket:196

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