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/2015_CO6_CO5_zenv_wr_direct_dwl_temp/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/2015_CO6_CO5_zenv_wr_direct_dwl_temp/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90 @ 5418

Last change on this file since 5418 was 5418, checked in by deazer, 9 years ago

Removed SVN KEYWORDS ready for adding code changes before fcm merges

File size: 11.3 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_diff      !: flag of perform or not the lateral diff.
36   LOGICAL , PUBLIC ::   ln_trcldf_lap       !: laplacian operator
37   LOGICAL , PUBLIC ::   ln_trcldf_bilap     !: bilaplacian operator
38   LOGICAL , PUBLIC ::   ln_trcldf_level     !: iso-level direction
39   LOGICAL , PUBLIC ::   ln_trcldf_hor       !: horizontal (geopotential) direction
40   LOGICAL , PUBLIC ::   ln_trcldf_iso       !: iso-neutral direction
41   REAL(wp), PUBLIC ::   rn_ahtrc_0          !: diffusivity coefficient for passive tracer (m2/s)
42   REAL(wp), PUBLIC ::   rn_ahtrb_0          !: background diffusivity coefficient for passive tracer (m2/s)
43
44   !                                        !!: ** Treatment of Negative concentrations ( nam_trcrad )
45   LOGICAL , PUBLIC ::   ln_trcrad           !: flag to artificially correct negative concentrations
46
47   !                                        !!: ** Vertical diffusion (nam_trczdf) **
48   LOGICAL , PUBLIC ::   ln_trczdf_exp       !: explicit vertical diffusion scheme flag
49   INTEGER , PUBLIC ::   nn_trczdf_exp       !: number of sub-time step (explicit time stepping)
50
51   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) **
52   !                          !!* Namelist namtrc_dmp : passive tracer newtonian damping *
53   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer
54   CHARACTER(LEN=200) , PUBLIC :: cn_resto_tr    !File containing restoration coefficient
55
56   !!----------------------------------------------------------------------
57   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
58   !! $Id$
59   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
60   !!----------------------------------------------------------------------
61
62CONTAINS
63
64   SUBROUTINE trc_nam_trp
65      !!----------------------------------------------------------------------
66      !!                  ***  ROUTINE trc_nam_trp  ***
67      !!               
68      !! ** Purpose :   Read Namelist for tracer transport option
69      !!----------------------------------------------------------------------
70      INTEGER ::  ios                 ! Local integer output status for namelist read
71      NAMELIST/namtrc_adv/ ln_trcadv_cen2 , ln_trcadv_tvd   ,    &
72         &                 ln_trcadv_muscl, ln_trcadv_muscl2,    &
73         &                 ln_trcadv_ubs  , ln_trcadv_qck, ln_trcadv_msc_ups
74
75      NAMELIST/namtrc_ldf/ ln_trcldf_diff , ln_trcldf_lap  ,     &
76         &                 ln_trcldf_bilap, ln_trcldf_level,     &
77         &                 ln_trcldf_hor  , ln_trcldf_iso  , rn_ahtrc_0, rn_ahtrb_0
78      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp
79      NAMELIST/namtrc_rad/ ln_trcrad
80      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr
81      !!----------------------------------------------------------------------
82
83      IF(lwp) WRITE(numout,*)
84      IF(lwp) WRITE(numout,*) ' trc_nam_trp: read namelist for tracer transport'
85      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
86
87      REWIND( numnat_ref )              ! Namelist namtrc_adv in reference namelist : Tracer advection scheme
88      READ  ( numnat_ref, namtrc_adv, IOSTAT = ios, ERR = 901)
89901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in reference namelist', lwp )
90
91      REWIND( numnat_cfg )              ! Namelist namtrc_adv in configuration namelist : Tracer advection scheme
92      READ  ( numnat_cfg, namtrc_adv, IOSTAT = ios, ERR = 902 )
93902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in configuration namelist', lwp )
94      IF(lwm) WRITE ( numont, namtrc_adv )
95
96      IF(lwp) THEN                    ! Namelist print
97         WRITE(numout,*)
98         WRITE(numout,*) 'trc_adv_ctl : choice/control of the tracer advection scheme'
99         WRITE(numout,*) '~~~~~~~~~~~'
100         WRITE(numout,*) '   Namelist namtrc_adv : chose a advection scheme for tracers'
101         WRITE(numout,*) '      2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
102         WRITE(numout,*) '      TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
103         WRITE(numout,*) '      MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
104         WRITE(numout,*) '      MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
105         WRITE(numout,*) '      UBS    advection scheme        ln_trcadv_ubs    = ', ln_trcadv_ubs
106         WRITE(numout,*) '      QUICKEST advection scheme      ln_trcadv_qck    = ', ln_trcadv_qck
107      ENDIF
108      !
109      REWIND( numnat_ref )              ! Namelist namtrc_ldf in reference namelist : Tracer lateral diffusive operator
110      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
111903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
112
113      REWIND( numnat_cfg )              ! Namelist namtrc_ldf in configuration namelist : Tracer lateral diffusive operator
114      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
115904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
116      IF(lwm) WRITE ( numont, namtrc_ldf )
117
118      IF(lwp) THEN                    ! Namelist print
119         WRITE(numout,*)
120         WRITE(numout,*) 'trc:ldf_ctl : lateral tracer diffusive operator'
121         WRITE(numout,*) '~~~~~~~~~~~'
122         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
123         WRITE(numout,*) '      perform lateral diffusion or not                   ln_trcldf_diff  = ', ln_trcldf_diff
124         WRITE(numout,*) '      laplacian operator                                 ln_trcldf_lap   = ', ln_trcldf_lap
125         WRITE(numout,*) '      bilaplacian operator                               ln_trcldf_bilap = ', ln_trcldf_bilap
126         WRITE(numout,*) '      iso-level                                          ln_trcldf_level = ', ln_trcldf_level
127         WRITE(numout,*) '      horizontal (geopotential)                          ln_trcldf_hor   = ', ln_trcldf_hor
128         WRITE(numout,*) '      iso-neutral                                        ln_trcldf_iso   = ', ln_trcldf_iso
129         WRITE(numout,*) '      diffusivity coefficient                                 rn_ahtrc_0 = ', rn_ahtrc_0
130         WRITE(numout,*) '      background hor. diffusivity                             rn_ahtrb_0 = ', rn_ahtrb_0
131      ENDIF
132
133      !                                ! Vertical mixing
134      REWIND( numnat_ref )              ! Namelist namtrc_zdf in reference namelist : Tracer vertical mixing
135      READ  ( numnat_ref, namtrc_zdf, IOSTAT = ios, ERR = 905)
136905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in reference namelist', lwp )
137
138      REWIND( numnat_cfg )              ! Namelist namtrc_zdf in configuration namelist : Tracer vertical mixing
139      READ  ( numnat_cfg, namtrc_zdf, IOSTAT = ios, ERR = 906 )
140906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in configuration namelist', lwp )
141      IF(lwm) WRITE ( numont, namtrc_zdf )
142
143      IF(lwp) THEN                     !   ! Control print
144         WRITE(numout,*)
145         WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion parameters'
146         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
147         WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp
148      ENDIF
149
150      !
151      REWIND( numnat_ref )              ! Namelist namtrc_rad in reference namelist : Tracer negative concentrations
152      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
153907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
154
155      REWIND( numnat_cfg )              ! Namelist namtrc_rad in configuration namelist : Tracer negative concentrations
156      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
157908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
158      IF(lwm) WRITE ( numont, namtrc_rad )
159
160      IF(lwp) THEN                     !   ! Control print
161         WRITE(numout,*)
162         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
163         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
164      ENDIF
165
166
167      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping
168      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909)
169909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist', lwp )
170
171      REWIND( numnat_cfg )              ! Namelist namtrc_dmp in configuration namelist : Passive tracers newtonian damping
172      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910)
173910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist', lwp )
174      IF(lwm) WRITE ( numont, namtrc_dmp )
175
176      IF(lwp) THEN                       ! Namelist print
177         WRITE(numout,*)
178         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
179         WRITE(numout,*) '~~~~~~~'
180         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
181         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)'
182         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr
183      ENDIF
184      !
185   END SUBROUTINE trc_nam_trp
186   
187#else
188   !!----------------------------------------------------------------------
189   !!   Dummy module :                                         No TOP model
190   !!----------------------------------------------------------------------
191CONTAINS
192   SUBROUTINE trc_nam_trp              ! Empty routine
193   END SUBROUTINE trc_nam_trp
194#endif
195
196  !!======================================================================
197END MODULE trcnam_trp
Note: See TracBrowser for help on using the repository browser.