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 branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/DEV_r1879_FCM/NEMOGCM/NEMO/TOP_SRC/TRP/trctrp_lec.F90 @ 2013

Last change on this file since 2013 was 2013, checked in by smasson, 14 years ago

remove propertie svn:executabe of fortran files in DEV_r1879_FCM

  • Property svn:keywords set to Id
File size: 12.2 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   !                                                 !!: ** Treatment of Negative concentrations ( nam_trcrad )
42   LOGICAL , PUBLIC ::   ln_trcrad       = .TRUE.     !: flag to artificially correct negative concentrations
43
44   !                                                 !!: flag of the lateral diff. scheme used
45   LOGICAL , PUBLIC ::   l_trcldf_lap                 !: iso-level laplacian operator
46   LOGICAL , PUBLIC ::   l_trcldf_bilap               !: iso-level bilaplacian operator
47   LOGICAL , PUBLIC ::   l_trcldf_bilapg              !: geopotential bilap. (s-coord)
48   LOGICAL , PUBLIC ::   l_trcldf_iso                 !: iso-neutral laplacian or horizontal lapacian (s-coord)
49   LOGICAL , PUBLIC ::   l_trczdf_iso                 !: idem for the vertical component
50   LOGICAL , PUBLIC ::   l_trczdf_iso_vo              !: idem with vectopt_memory
51   LOGICAL , PUBLIC ::   l_trcldf_iso_zps             !: iso-neutral laplacian (partial steps)
52
53   !                                                 !!: ** Vertical diffusion (nam_trczdf) **
54   LOGICAL , PUBLIC ::   ln_trczdf_exp = .FALSE.      !: explicit vertical diffusion scheme flag
55
56   !                                                 !!: ** vertical diffusion (namzdf) **
57   INTEGER , PUBLIC ::   n_trczdf_exp = 3             !: number of sub-time step (explicit time stepping)
58
59   LOGICAL , PUBLIC ::   l_trczdf_exp     = .FALSE.   !: explicit vertical diffusion
60   LOGICAL , PUBLIC ::   l_trczdf_imp     = .FALSE.   !: implicit vertical diffusion
61
62#if defined key_trcdmp
63   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) **
64   INTEGER  , PUBLIC ::   ndmptr   =   -1             !: = 0/-1/'latitude' for damping over tracers
65   INTEGER  , PUBLIC ::   ndmpftr  =    2             !: = 1 create a damping.coeff NetCDF file
66   INTEGER  , PUBLIC ::   nmldmptr =    0             !: = 0/1/2 flag for damping in the mixed layer
67
68   !                                                 !!: ** newtonian damping (namdmp) **
69   REAL(wp) , PUBLIC ::   sdmptr   =   50.            !: surface time scale for internal damping (days)
70   REAL(wp) , PUBLIC ::   bdmptr   =  360.            !: bottom time scale for internal damping (days)
71   REAL(wp) , PUBLIC ::   hdmptr   =  800.            !: depth of transition between sdmp and bdmp (meters)
72#endif
73   !                                                 !!: ** SMOLAR advection scheme
74   REAL(wp) , PUBLIC ::  rsc       = 1.               !: tuning coefficient for anti-diffusion
75   INTEGER  , PUBLIC ::  ncortrc   = 1                !: number of corrective phases
76   LOGICAL  , PUBLIC ::  crosster  = .FALSE.          !: computes crossterms (T) or not (F)
77   !!----------------------------------------------------------------------
78   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
79   !! $Id$
80   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
81   !!----------------------------------------------------------------------
82
83CONTAINS
84
85   SUBROUTINE trc_trp_lec
86      !!----------------------------------------------------------------------
87      !!                  ***  ROUTINE trc_trp_lec  ***
88      !!               
89      !! ** Purpose :   Read Namelist for tracer transport option
90      !!----------------------------------------------------------------------
91      NAMELIST/namtopadv/ ln_trcadv_cen2 , ln_trcadv_tvd,   &
92         &                ln_trcadv_muscl, ln_trcadv_muscl2, ln_trcadv_smolar, &
93         &                rsc, ncortrc, crosster
94#if  defined key_trcbbl_dif   ||   defined key_trcbbl_adv 
95      NAMELIST/namtopbbl/ atrcbbl
96#endif
97      NAMELIST/namtopldf/  ln_trcldf_diff  , ln_trcldf_lap  , ln_trcldf_bilap, &
98         &                 ln_trcldf_level, ln_trcldf_hor, ln_trcldf_iso,   &
99         &                 ahtrc0, ahtrb0, aeivtr0, trcrat
100      NAMELIST/namtopzdf/ ln_trczdf_exp, n_trczdf_exp
101      NAMELIST/namtoprad/ ln_trcrad
102#if defined key_trcdmp
103      NAMELIST/namtopdmp/ ndmptr, ndmpftr, nmldmptr, sdmptr, bdmptr, hdmptr
104#endif
105      !!----------------------------------------------------------------------
106
107      IF(lwp) WRITE(numout,*)
108      IF(lwp) WRITE(numout,*) ' trc_trp_lec: read namelist for tracer transport'
109      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
110
111      !                                ! tracer advection scheme
112      REWIND( numnat )                 !   ! Read Namelist namtopadv
113      READ  ( numnat, namtopadv )
114
115      IF(lwp) THEN                     !   ! Control print
116         WRITE(numout,*)
117         WRITE(numout,*) '   Namelist namtopadv : chose a advection scheme for tracers'
118         WRITE(numout,*) '      2nd order advection scheme               ln_trcadv_cen2   = ', ln_trcadv_cen2
119         WRITE(numout,*) '      TVD advection scheme                     ln_trcadv_tvd    = ', ln_trcadv_tvd
120         WRITE(numout,*) '      MUSCL  advection scheme                  ln_trcadv_muscl  = ', ln_trcadv_muscl
121         WRITE(numout,*) '      MUSCL2 advection scheme                  ln_trcadv_muscl2 = ', ln_trcadv_muscl2
122         WRITE(numout,*) '      SMOLARKIEWICZ advection scheme           ln_trcadv_smolar = ', ln_trcadv_smolar
123         IF( ln_trcadv_smolar ) THEN
124            WRITE(numout,*) '      SMOLARKIEWICZ : tuning coefficient                rsc      = ', rsc
125            WRITE(numout,*) '      SMOLARKIEWICZ : number of corrective phase        ncortrc  = ', ncortrc
126            WRITE(numout,*) '      SMOLARKIEWICZ : computes or not crossterms        crosster = ', crosster
127         ENDIF
128      ENDIF
129
130#if  defined key_trcbbl_dif
131      !                                ! Bottom boundary layer
132      REWIND( numnat )                 !   ! Read Namelist namtopbbl
133      READ  ( numnat, namtopbbl )
134
135      IF(lwp) THEN                     !   ! Control print
136         WRITE(numout,*)
137         WRITE(numout,*) '   Namelist namtopbbl : set Diffusive Bottom Boundary Layer parameters'
138         WRITE(numout,*) '      bottom boundary layer coef.    atrcbbl = ', atrcbbl
139# if defined key_trcbbl_adv
140         WRITE(numout,*) '   * Advective Bottom Boundary Layer'
141# endif
142      ENDIF
143#endif
144
145      !                                ! Lateral physics on tracers   
146      REWIND( numnat )                 !   ! Read Namelist namtopldf
147      READ  ( numnat, namtopldf )
148
149      IF(lwp) THEN                     !   ! Control print
150         WRITE(numout,*)
151         WRITE(numout,*) '   Namelist namtopldf : set lateral mixing parameters (type, direction, coefficients)'
152         WRITE(numout,*) '      perform lateral diffusion or not               ln_trcldf_diff  = ', ln_trcldf_diff
153         WRITE(numout,*) '      laplacian operator                             ln_trcldf_lap   = ', ln_trcldf_lap
154         WRITE(numout,*) '      bilaplacian operator                           ln_trcldf_bilap = ', ln_trcldf_bilap
155         WRITE(numout,*) '      iso-level                                      ln_trcldf_level = ', ln_trcldf_level
156         WRITE(numout,*) '      horizontal (geopotential)                      ln_trcldf_hor   = ', ln_trcldf_hor
157         WRITE(numout,*) '      iso-neutral                                    ln_trcldf_iso   = ', ln_trcldf_iso
158         WRITE(numout,*) '      lateral eddy diffusivity                              ahtrc0   = ', ahtrc0
159         WRITE(numout,*) '      background hor. diffusivity                            ahtrb0  = ', ahtrb0
160         WRITE(numout,*) '      eddy induced velocity coef.                           aeivtr0  = ', aeivtr0
161         WRITE(numout,*) '      ratio between passive and active tracer diffusion coef  trcrat = ', trcrat
162      ENDIF
163
164      !                                ! Vertical mixing
165      REWIND( numnat )                 !   ! Read namtopzdf namelist
166      READ  ( numnat, namtopzdf )
167
168      IF(lwp) THEN                     !   ! Control print
169         WRITE(numout,*)
170         WRITE(numout,*) '   Namelist namtopzdf : set vertical diffusion parameters'
171         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
172         WRITE(numout,*) '      number of time step               n_trczdf_exp = ', n_trczdf_exp
173      ENDIF
174
175      !
176      REWIND( numnat )                 !   Read Namelist namtoprad
177      READ  ( numnat, namtoprad )
178
179      IF(lwp) THEN                     !   ! Control print
180         WRITE(numout,*)
181         WRITE(numout,*) '   Namelist namtoprad : treatment of negative concentrations'
182         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
183      ENDIF
184
185
186# if defined key_trcdmp
187      !                                ! passive tracres damping term
188      REWIND( numnat )                 !   ! Read Namelist namtdp
189      READ  ( numnat, namtopdmp )
190      IF( lzoom )   nmldmptr = 0           ! restoring to climatology at closed north or south boundaries
191
192      IF(lwp) THEN                     !   ! Control print
193         WRITE(numout,*)
194         WRITE(numout,*) '   Namelist namtopdmp : set damping parameter'
195         WRITE(numout,*) '      tracers damping option         ndmptr   = ', ndmptr
196         WRITE(numout,*) '      create a damping.coeff file    ndmpftr  = ', ndmpftr
197         WRITE(numout,*) '      mixed layer damping option     nmldmptr = ', nmldmptr, '(zoom: forced to 0)'
198         WRITE(numout,*) '      surface time scale (days)      sdmptr   = ', sdmptr
199         WRITE(numout,*) '      bottom time scale (days)       bdmptr   = ', bdmptr
200         WRITE(numout,*) '      depth of transition (meters)   hdmptr   = ', hdmptr
201      ENDIF
202#endif
203      !
204   END SUBROUTINE trc_trp_lec
205   
206#else
207   !!----------------------------------------------------------------------
208   !!   Dummy module :                                         No TOP model
209   !!----------------------------------------------------------------------
210CONTAINS
211   SUBROUTINE trc_trp_lec              ! Empty routine
212   END SUBROUTINE trc_trp_lec
213#endif
214
215  !!======================================================================
216END MODULE trctrp_lec
Note: See TracBrowser for help on using the repository browser.