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.
trcnam_trp.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 13 years ago

update licence of all NEMO files...

  • Property svn:keywords set to Id
File size: 9.8 KB
Line 
1MODULE trcnam_trp
2   !!======================================================================
3   !!                       ***  MODULE  trcnam_trp  ***
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_nam_trp  : read the passive tracer namelist for transport
14   !!----------------------------------------------------------------------
15   USE trc                 ! ocean passive tracers variables
16   USE in_out_manager      ! ocean dynamics and active tracers variables
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC   trc_nam_trp    ! routine called by step module
22 
23   !                                                 !!: ** Advection (nam_trcadv) **
24   LOGICAL , PUBLIC ::   ln_trcadv_cen2   = .FALSE.   ! 2nd order centered scheme flag
25   LOGICAL , PUBLIC ::   ln_trcadv_tvd    = .TRUE.    ! 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_ubs    = .FALSE.   ! UBS scheme flag
29   LOGICAL , PUBLIC ::   ln_trcadv_qck    = .FALSE.   ! QUICKEST scheme flag
30
31   !                                                 !!: ** lateral mixing namelist (nam_trcldf) **
32   LOGICAL , PUBLIC ::   ln_trcldf_diff  = .FALSE.    !: flag of perform or not the lateral diff.
33   LOGICAL , PUBLIC ::   ln_trcldf_lap   = .TRUE.     !: laplacian operator
34   LOGICAL , PUBLIC ::   ln_trcldf_bilap = .FALSE.    !: bilaplacian operator
35   LOGICAL , PUBLIC ::   ln_trcldf_level = .FALSE.    !: iso-level direction
36   LOGICAL , PUBLIC ::   ln_trcldf_hor   = .FALSE.    !: horizontal (geopotential) direction
37   LOGICAL , PUBLIC ::   ln_trcldf_iso   = .TRUE.     !: iso-neutral direction
38   REAL(wp), PUBLIC ::   rn_ahtrb_0                   !: background diffusivity coefficient for passive tracer (m2/s)
39
40   !                                                 !!: ** Treatment of Negative concentrations ( nam_trcrad )
41   LOGICAL , PUBLIC ::   ln_trcrad       = .TRUE.     !: flag to artificially correct negative concentrations
42
43   !                                                 !!: ** Vertical diffusion (nam_trczdf) **
44   LOGICAL , PUBLIC ::   ln_trczdf_exp = .FALSE.      !: explicit vertical diffusion scheme flag
45   INTEGER , PUBLIC ::   nn_trczdf_exp = 3             !: number of sub-time step (explicit time stepping)
46
47
48#if defined key_trcdmp
49   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) **
50   INTEGER , PUBLIC ::   nn_hdmp_tr      =   -1       ! = 0/-1/'latitude' for damping over passive tracer
51   INTEGER , PUBLIC ::   nn_zdmp_tr      =    0       ! = 0/1/2 flag for damping in the mixed layer
52   REAL(wp), PUBLIC ::   rn_surf_tr      =   50.      ! surface time scale for internal damping        [days]
53   REAL(wp), PUBLIC ::   rn_bot_tr       =  360.      ! bottom time scale for internal damping         [days]
54   REAL(wp), PUBLIC ::   rn_dep_tr       =  800.      ! depth of transition between rn_surf and rn_bot [meters]
55   INTEGER , PUBLIC ::   nn_file_tr      =    2       ! = 1 create a damping.coeff NetCDF file
56#endif
57
58   !!----------------------------------------------------------------------
59   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
60   !! $Id$
61   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
62   !!----------------------------------------------------------------------
63
64CONTAINS
65
66   SUBROUTINE trc_nam_trp
67      !!----------------------------------------------------------------------
68      !!                  ***  ROUTINE trc_nam_trp  ***
69      !!               
70      !! ** Purpose :   Read Namelist for tracer transport option
71      !!----------------------------------------------------------------------
72      NAMELIST/namtrc_adv/ ln_trcadv_cen2 , ln_trcadv_tvd   ,    &
73         &                 ln_trcadv_muscl, ln_trcadv_muscl2,    &
74         &                 ln_trcadv_ubs  , ln_trcadv_qck
75
76      NAMELIST/namtrc_ldf/ ln_trcldf_diff , ln_trcldf_lap  ,     &
77         &                 ln_trcldf_bilap, ln_trcldf_level,     &
78         &                 ln_trcldf_hor  , ln_trcldf_iso  , rn_ahtrb_0
79      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp
80      NAMELIST/namtrc_rad/ ln_trcrad
81#if defined key_trcdmp
82      NAMELIST/namtrc_dmp/ nn_hdmp_tr, nn_zdmp_tr, rn_surf_tr, &
83        &                  rn_bot_tr , rn_dep_tr , nn_file_tr
84#endif
85      !!----------------------------------------------------------------------
86
87      IF(lwp) WRITE(numout,*)
88      IF(lwp) WRITE(numout,*) ' trc_nam_trp: read namelist for tracer transport'
89      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
90
91      REWIND ( numnat )               ! Read Namelist namtrc_adv : tracer advection scheme
92      READ   ( numnat, namtrc_adv )
93
94      IF(lwp) THEN                    ! Namelist print
95         WRITE(numout,*)
96         WRITE(numout,*) 'trc_adv_ctl : choice/control of the tracer advection scheme'
97         WRITE(numout,*) '~~~~~~~~~~~'
98         WRITE(numout,*) '   Namelist namtrc_adv : chose a advection scheme for tracers'
99         WRITE(numout,*) '      2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
100         WRITE(numout,*) '      TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
101         WRITE(numout,*) '      MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
102         WRITE(numout,*) '      MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
103         WRITE(numout,*) '      UBS    advection scheme        ln_trcadv_ubs    = ', ln_trcadv_ubs
104         WRITE(numout,*) '      QUICKEST advection scheme      ln_trcadv_qck    = ', ln_trcadv_qck
105      ENDIF
106      !
107      REWIND( numnat )                ! Namelist namtrc_ldf
108      READ  ( numnat, namtrc_ldf )
109
110      IF(lwp) THEN                    ! Namelist print
111         WRITE(numout,*)
112         WRITE(numout,*) 'trc:ldf_ctl : lateral tracer diffusive operator'
113         WRITE(numout,*) '~~~~~~~~~~~'
114         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
115         WRITE(numout,*) '      perform lateral diffusion or not                   ln_trcldf_diff  = ', ln_trcldf_diff
116         WRITE(numout,*) '      laplacian operator                                 ln_trcldf_lap   = ', ln_trcldf_lap
117         WRITE(numout,*) '      bilaplacian operator                               ln_trcldf_bilap = ', ln_trcldf_bilap
118         WRITE(numout,*) '      iso-level                                          ln_trcldf_level = ', ln_trcldf_level
119         WRITE(numout,*) '      horizontal (geopotential)                          ln_trcldf_hor   = ', ln_trcldf_hor
120         WRITE(numout,*) '      iso-neutral                                        ln_trcldf_iso   = ', ln_trcldf_iso
121         WRITE(numout,*) '      background hor. diffusivity                             rn_ahtrb_0 = ', rn_ahtrb_0
122      ENDIF
123
124      !                                ! Vertical mixing
125      REWIND( numnat )                 !   ! Read namtopzdf namelist
126      READ  ( numnat, namtrc_zdf )
127
128      IF(lwp) THEN                     !   ! Control print
129         WRITE(numout,*)
130         WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion parameters'
131         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
132         WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp
133      ENDIF
134
135      !
136      REWIND( numnat )                 !   Read Namelist namtoprad
137      READ  ( numnat, namtrc_rad )
138
139      IF(lwp) THEN                     !   ! Control print
140         WRITE(numout,*)
141         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
142         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
143      ENDIF
144
145
146# if defined key_trcdmp
147      REWIND ( numnat )                  ! Read Namelist namtra_dmp : temperature and salinity damping term
148      READ   ( numnat, namtrc_dmp )
149      IF( lzoom )   nn_zdmp_trc = 0           ! restoring to climatology at closed north or south boundaries
150
151      IF(lwp) THEN                       ! Namelist print
152         WRITE(numout,*)
153         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
154         WRITE(numout,*) '~~~~~~~'
155         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
156         WRITE(numout,*) '      tracer damping option          nn_hdmp_tr = ', nn_hdmp_tr
157         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)'
158         WRITE(numout,*) '      surface time scale (days)      rn_surf_tr = ', rn_surf_tr
159         WRITE(numout,*) '      bottom time scale (days)       rn_bot_tr  = ', rn_bot_tr
160         WRITE(numout,*) '      depth of transition (meters)   rn_dep_tr  = ', rn_dep_tr
161         WRITE(numout,*) '      create a damping.coeff file    nn_file_tr = ', nn_file_tr
162      ENDIF
163#endif
164      !
165   END SUBROUTINE trc_nam_trp
166   
167#else
168   !!----------------------------------------------------------------------
169   !!   Dummy module :                                         No TOP model
170   !!----------------------------------------------------------------------
171CONTAINS
172   SUBROUTINE trc_nam_trp              ! Empty routine
173   END SUBROUTINE trc_nam_trp
174#endif
175
176  !!======================================================================
177END MODULE trcnam_trp
Note: See TracBrowser for help on using the repository browser.