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/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/2012/dev_MERGE_2012/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90 @ 3718

Last change on this file since 3718 was 3718, checked in by cetlod, 11 years ago

dev_MERGE_2012 : modification in MUSCL routines ; needed to be able to use the upstream parametisation with passive tracers

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