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

source: branches/UKMO/AMM15_v3_6_STABLE_package_collate/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90 @ 11063

Last change on this file since 11063 was 11063, checked in by dford, 5 years ago

Add missing lbc_lnk and option to relax chlorophyll to climatology. See Met Office utils ticket 216.

File size: 11.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                 ! passive tracers variables
16   USE in_out_manager      ! ocean dynamics and active tracers variables
17   USE lib_mpp           ! distributed memory computing library
18   USE fldread
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   trc_nam_trp    ! routine called by step module
24 
25   !                                        !!: ** Advection (namtrc_adv) **
26   LOGICAL , PUBLIC ::   ln_trcadv_cen2      ! 2nd order centered scheme flag
27   LOGICAL , PUBLIC ::   ln_trcadv_tvd       ! TVD scheme flag
28   LOGICAL , PUBLIC ::   ln_trcadv_muscl     ! MUSCL scheme flag
29   LOGICAL , PUBLIC ::   ln_trcadv_muscl2    ! MUSCL2 scheme flag
30   LOGICAL , PUBLIC ::   ln_trcadv_ubs       ! UBS scheme flag
31   LOGICAL , PUBLIC ::   ln_trcadv_qck       ! QUICKEST scheme flag
32   LOGICAL , PUBLIC ::   ln_trcadv_msc_ups   ! use upstream scheme within muscl
33
34
35   !                                        !!: ** lateral mixing namelist (nam_trcldf) **
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   CHARACTER(LEN=200) , PUBLIC :: cn_dir_chldmp = './'    !: Directory containing chlorophyll file
56   INTEGER , PUBLIC ::    nn_chldmp = 0    !: = 0/1/2 flag for surface chlorophyll damping
57   REAL(wp), PUBLIC ::    rn_chldmp = 0.0  !: chlorophyll damping coefficient
58   TYPE(FLD_N), PUBLIC :: sn_chldmp        !: informations about the fields to be read
59
60   !!----------------------------------------------------------------------
61   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
62   !! $Id$
63   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
64   !!----------------------------------------------------------------------
65
66CONTAINS
67
68   SUBROUTINE trc_nam_trp
69      !!----------------------------------------------------------------------
70      !!                  ***  ROUTINE trc_nam_trp  ***
71      !!               
72      !! ** Purpose :   Read Namelist for tracer transport option
73      !!----------------------------------------------------------------------
74      INTEGER ::  ios                 ! Local integer output status for namelist read
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_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      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr, cn_dir_chldmp, nn_chldmp, &
85         &                 sn_chldmp  , rn_chldmp
86      !!----------------------------------------------------------------------
87
88      IF(lwp) WRITE(numout,*)
89      IF(lwp) WRITE(numout,*) ' trc_nam_trp: read namelist for tracer transport'
90      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
91
92      REWIND( numnat_ref )              ! Namelist namtrc_adv in reference namelist : Tracer advection scheme
93      READ  ( numnat_ref, namtrc_adv, IOSTAT = ios, ERR = 901)
94901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in reference namelist', lwp )
95
96      REWIND( numnat_cfg )              ! Namelist namtrc_adv in configuration namelist : Tracer advection scheme
97      READ  ( numnat_cfg, namtrc_adv, IOSTAT = ios, ERR = 902 )
98902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in configuration namelist', lwp )
99      IF(lwm) WRITE ( numont, namtrc_adv )
100
101      IF(lwp) THEN                    ! Namelist print
102         WRITE(numout,*)
103         WRITE(numout,*) 'trc_adv_ctl : choice/control of the tracer advection scheme'
104         WRITE(numout,*) '~~~~~~~~~~~'
105         WRITE(numout,*) '   Namelist namtrc_adv : chose a advection scheme for tracers'
106         WRITE(numout,*) '      2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
107         WRITE(numout,*) '      TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
108         WRITE(numout,*) '      MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
109         WRITE(numout,*) '      MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
110         WRITE(numout,*) '      UBS    advection scheme        ln_trcadv_ubs    = ', ln_trcadv_ubs
111         WRITE(numout,*) '      QUICKEST advection scheme      ln_trcadv_qck    = ', ln_trcadv_qck
112      ENDIF
113      !
114      REWIND( numnat_ref )              ! Namelist namtrc_ldf in reference namelist : Tracer lateral diffusive operator
115      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
116903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
117
118      REWIND( numnat_cfg )              ! Namelist namtrc_ldf in configuration namelist : Tracer lateral diffusive operator
119      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
120904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
121      IF(lwm) WRITE ( numont, namtrc_ldf )
122
123      IF(lwp) THEN                    ! Namelist print
124         WRITE(numout,*)
125         WRITE(numout,*) 'trc:ldf_ctl : lateral tracer diffusive operator'
126         WRITE(numout,*) '~~~~~~~~~~~'
127         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
128         WRITE(numout,*) '      laplacian operator                                 ln_trcldf_lap   = ', ln_trcldf_lap
129         WRITE(numout,*) '      bilaplacian operator                               ln_trcldf_bilap = ', ln_trcldf_bilap
130         WRITE(numout,*) '      iso-level                                          ln_trcldf_level = ', ln_trcldf_level
131         WRITE(numout,*) '      horizontal (geopotential)                          ln_trcldf_hor   = ', ln_trcldf_hor
132         WRITE(numout,*) '      iso-neutral                                        ln_trcldf_iso   = ', ln_trcldf_iso
133         WRITE(numout,*) '      diffusivity coefficient                                 rn_ahtrc_0 = ', rn_ahtrc_0
134         WRITE(numout,*) '      background hor. diffusivity                             rn_ahtrb_0 = ', rn_ahtrb_0
135      ENDIF
136
137      !                                ! Vertical mixing
138      REWIND( numnat_ref )              ! Namelist namtrc_zdf in reference namelist : Tracer vertical mixing
139      READ  ( numnat_ref, namtrc_zdf, IOSTAT = ios, ERR = 905)
140905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in reference namelist', lwp )
141
142      REWIND( numnat_cfg )              ! Namelist namtrc_zdf in configuration namelist : Tracer vertical mixing
143      READ  ( numnat_cfg, namtrc_zdf, IOSTAT = ios, ERR = 906 )
144906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in configuration namelist', lwp )
145      IF(lwm) WRITE ( numont, namtrc_zdf )
146
147      IF(lwp) THEN                     !   ! Control print
148         WRITE(numout,*)
149         WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion parameters'
150         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
151         WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp
152      ENDIF
153
154      !
155      REWIND( numnat_ref )              ! Namelist namtrc_rad in reference namelist : Tracer negative concentrations
156      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
157907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
158
159      REWIND( numnat_cfg )              ! Namelist namtrc_rad in configuration namelist : Tracer negative concentrations
160      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
161908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
162      IF(lwm) WRITE ( numont, namtrc_rad )
163
164      IF(lwp) THEN                     !   ! Control print
165         WRITE(numout,*)
166         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
167         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
168      ENDIF
169
170
171      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping
172      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909)
173909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist', lwp )
174
175      REWIND( numnat_cfg )              ! Namelist namtrc_dmp in configuration namelist : Passive tracers newtonian damping
176      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910)
177910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist', lwp )
178      IF(lwm) WRITE ( numont, namtrc_dmp )
179
180      IF(lwp) THEN                       ! Namelist print
181         WRITE(numout,*)
182         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
183         WRITE(numout,*) '~~~~~~~'
184         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
185         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)'
186         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr
187         WRITE(numout,*) '      Surface chlorophyll damping     nn_chldmp = ', nn_chldmp
188         WRITE(numout,*) '      Damping coefficient             rn_chldmp = ', rn_chldmp
189         WRITE(numout,*) '      Chlorophyll directory       cn_dir_chldmp = ', cn_dir_chldmp
190      ENDIF
191      !
192   END SUBROUTINE trc_nam_trp
193   
194#else
195   !!----------------------------------------------------------------------
196   !!   Dummy module :                                         No TOP model
197   !!----------------------------------------------------------------------
198CONTAINS
199   SUBROUTINE trc_nam_trp              ! Empty routine
200   END SUBROUTINE trc_nam_trp
201#endif
202
203  !!======================================================================
204END MODULE trcnam_trp
Note: See TracBrowser for help on using the repository browser.