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/UKMO/dev_r5518_FOAM_local/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/dev_r5518_FOAM_local/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90 @ 5615

Last change on this file since 5615 was 5615, checked in by cguiavarch, 9 years ago

Clear svn keywords

File size: 11.1 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                 ! passive tracers variables
16   USE in_out_manager      ! ocean dynamics and active tracers variables
17   USE lib_mpp           ! distributed memory computing library
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   trc_nam_trp    ! routine called by step module
23 
24   !                                        !!: ** Advection (namtrc_adv) **
25   LOGICAL , PUBLIC ::   ln_trcadv_cen2      ! 2nd order centered scheme flag
26   LOGICAL , PUBLIC ::   ln_trcadv_tvd       ! TVD scheme flag
27   LOGICAL , PUBLIC ::   ln_trcadv_muscl     ! MUSCL scheme flag
28   LOGICAL , PUBLIC ::   ln_trcadv_muscl2    ! MUSCL2 scheme flag
29   LOGICAL , PUBLIC ::   ln_trcadv_ubs       ! UBS scheme flag
30   LOGICAL , PUBLIC ::   ln_trcadv_qck       ! QUICKEST scheme flag
31   LOGICAL , PUBLIC ::   ln_trcadv_msc_ups   ! use upstream scheme within muscl
32
33
34   !                                        !!: ** lateral mixing namelist (nam_trcldf) **
35   LOGICAL , PUBLIC ::   ln_trcldf_lap       !: laplacian operator
36   LOGICAL , PUBLIC ::   ln_trcldf_bilap     !: bilaplacian operator
37   LOGICAL , PUBLIC ::   ln_trcldf_level     !: iso-level direction
38   LOGICAL , PUBLIC ::   ln_trcldf_hor       !: horizontal (geopotential) direction
39   LOGICAL , PUBLIC ::   ln_trcldf_iso       !: 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           !: flag to artificially correct negative concentrations
45
46   !                                        !!: ** Vertical diffusion (nam_trczdf) **
47   LOGICAL , PUBLIC ::   ln_trczdf_exp       !: explicit vertical diffusion scheme flag
48   INTEGER , PUBLIC ::   nn_trczdf_exp       !: number of sub-time step (explicit time stepping)
49
50   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) **
51   !                          !!* Namelist namtrc_dmp : passive tracer newtonian damping *
52   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer
53   CHARACTER(LEN=200) , PUBLIC :: cn_resto_tr    !File containing restoration coefficient
54
55   !!----------------------------------------------------------------------
56   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
57   !! $Id$
58   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
59   !!----------------------------------------------------------------------
60
61CONTAINS
62
63   SUBROUTINE trc_nam_trp
64      !!----------------------------------------------------------------------
65      !!                  ***  ROUTINE trc_nam_trp  ***
66      !!               
67      !! ** Purpose :   Read Namelist for tracer transport option
68      !!----------------------------------------------------------------------
69      INTEGER ::  ios                 ! Local integer output status for namelist read
70      NAMELIST/namtrc_adv/ ln_trcadv_cen2 , ln_trcadv_tvd   ,    &
71         &                 ln_trcadv_muscl, ln_trcadv_muscl2,    &
72         &                 ln_trcadv_ubs  , ln_trcadv_qck, ln_trcadv_msc_ups
73
74      NAMELIST/namtrc_ldf/ ln_trcldf_lap  ,     &
75         &                 ln_trcldf_bilap, ln_trcldf_level,     &
76         &                 ln_trcldf_hor  , ln_trcldf_iso  , rn_ahtrc_0, rn_ahtrb_0
77      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp
78      NAMELIST/namtrc_rad/ ln_trcrad
79      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr
80      !!----------------------------------------------------------------------
81
82      IF(lwp) WRITE(numout,*)
83      IF(lwp) WRITE(numout,*) ' trc_nam_trp: read namelist for tracer transport'
84      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
85
86      REWIND( numnat_ref )              ! Namelist namtrc_adv in reference namelist : Tracer advection scheme
87      READ  ( numnat_ref, namtrc_adv, IOSTAT = ios, ERR = 901)
88901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in reference namelist', lwp )
89
90      REWIND( numnat_cfg )              ! Namelist namtrc_adv in configuration namelist : Tracer advection scheme
91      READ  ( numnat_cfg, namtrc_adv, IOSTAT = ios, ERR = 902 )
92902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in configuration namelist', lwp )
93      IF(lwm) WRITE ( numont, namtrc_adv )
94
95      IF(lwp) THEN                    ! Namelist print
96         WRITE(numout,*)
97         WRITE(numout,*) 'trc_adv_ctl : choice/control of the tracer advection scheme'
98         WRITE(numout,*) '~~~~~~~~~~~'
99         WRITE(numout,*) '   Namelist namtrc_adv : chose a advection scheme for tracers'
100         WRITE(numout,*) '      2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
101         WRITE(numout,*) '      TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
102         WRITE(numout,*) '      MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
103         WRITE(numout,*) '      MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
104         WRITE(numout,*) '      UBS    advection scheme        ln_trcadv_ubs    = ', ln_trcadv_ubs
105         WRITE(numout,*) '      QUICKEST advection scheme      ln_trcadv_qck    = ', ln_trcadv_qck
106      ENDIF
107      !
108      REWIND( numnat_ref )              ! Namelist namtrc_ldf in reference namelist : Tracer lateral diffusive operator
109      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
110903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
111
112      REWIND( numnat_cfg )              ! Namelist namtrc_ldf in configuration namelist : Tracer lateral diffusive operator
113      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
114904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
115      IF(lwm) WRITE ( numont, namtrc_ldf )
116
117      IF(lwp) THEN                    ! Namelist print
118         WRITE(numout,*)
119         WRITE(numout,*) 'trc:ldf_ctl : lateral tracer diffusive operator'
120         WRITE(numout,*) '~~~~~~~~~~~'
121         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
122         WRITE(numout,*) '      laplacian operator                                 ln_trcldf_lap   = ', ln_trcldf_lap
123         WRITE(numout,*) '      bilaplacian operator                               ln_trcldf_bilap = ', ln_trcldf_bilap
124         WRITE(numout,*) '      iso-level                                          ln_trcldf_level = ', ln_trcldf_level
125         WRITE(numout,*) '      horizontal (geopotential)                          ln_trcldf_hor   = ', ln_trcldf_hor
126         WRITE(numout,*) '      iso-neutral                                        ln_trcldf_iso   = ', ln_trcldf_iso
127         WRITE(numout,*) '      diffusivity coefficient                                 rn_ahtrc_0 = ', rn_ahtrc_0
128         WRITE(numout,*) '      background hor. diffusivity                             rn_ahtrb_0 = ', rn_ahtrb_0
129      ENDIF
130
131      !                                ! Vertical mixing
132      REWIND( numnat_ref )              ! Namelist namtrc_zdf in reference namelist : Tracer vertical mixing
133      READ  ( numnat_ref, namtrc_zdf, IOSTAT = ios, ERR = 905)
134905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in reference namelist', lwp )
135
136      REWIND( numnat_cfg )              ! Namelist namtrc_zdf in configuration namelist : Tracer vertical mixing
137      READ  ( numnat_cfg, namtrc_zdf, IOSTAT = ios, ERR = 906 )
138906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in configuration namelist', lwp )
139      IF(lwm) WRITE ( numont, namtrc_zdf )
140
141      IF(lwp) THEN                     !   ! Control print
142         WRITE(numout,*)
143         WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion parameters'
144         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
145         WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp
146      ENDIF
147
148      !
149      REWIND( numnat_ref )              ! Namelist namtrc_rad in reference namelist : Tracer negative concentrations
150      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
151907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
152
153      REWIND( numnat_cfg )              ! Namelist namtrc_rad in configuration namelist : Tracer negative concentrations
154      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
155908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
156      IF(lwm) WRITE ( numont, namtrc_rad )
157
158      IF(lwp) THEN                     !   ! Control print
159         WRITE(numout,*)
160         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
161         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
162      ENDIF
163
164
165      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping
166      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909)
167909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist', lwp )
168
169      REWIND( numnat_cfg )              ! Namelist namtrc_dmp in configuration namelist : Passive tracers newtonian damping
170      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910)
171910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist', lwp )
172      IF(lwm) WRITE ( numont, namtrc_dmp )
173
174      IF(lwp) THEN                       ! Namelist print
175         WRITE(numout,*)
176         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
177         WRITE(numout,*) '~~~~~~~'
178         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
179         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)'
180         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr
181      ENDIF
182      !
183   END SUBROUTINE trc_nam_trp
184   
185#else
186   !!----------------------------------------------------------------------
187   !!   Dummy module :                                         No TOP model
188   !!----------------------------------------------------------------------
189CONTAINS
190   SUBROUTINE trc_nam_trp              ! Empty routine
191   END SUBROUTINE trc_nam_trp
192#endif
193
194  !!======================================================================
195END MODULE trcnam_trp
Note: See TracBrowser for help on using the repository browser.