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_v3.4_asm_nemovar_community/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/TOP_SRC/TRP/trcnam_trp.F90 @ 6617

Last change on this file since 6617 was 6617, checked in by kingr, 8 years ago

Merged branches/UKMO/nemo_v3_6_STABLE_copy@6436

File size: 11.4 KB
RevLine 
[2030]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   !!----------------------------------------------------------------------
[4148]15   USE trc                 ! passive tracers variables
[2030]16   USE in_out_manager      ! ocean dynamics and active tracers variables
[4147]17   USE lib_mpp           ! distributed memory computing library
[2030]18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   trc_nam_trp    ! routine called by step module
23 
[4147]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
[2030]32
[3718]33
[4147]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)
[6617]42   REAL(wp), PUBLIC ::   rn_fact_lap         !: Enhanced zonal diffusivity coefficent in the equatorial domain
[2030]43
[4147]44   !                                        !!: ** Treatment of Negative concentrations ( nam_trcrad )
45   LOGICAL , PUBLIC ::   ln_trcrad           !: flag to artificially correct negative concentrations
[2030]46
[4147]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)
[2030]50
51   !                                                 !!: ** newtonian damping namelist (nam_trcdmp) **
[4148]52   !                          !!* Namelist namtrc_dmp : passive tracer newtonian damping *
53   INTEGER , PUBLIC ::   nn_zdmp_tr    ! = 0/1/2 flag for damping in the mixed layer
[5102]54   CHARACTER(LEN=200) , PUBLIC :: cn_resto_tr    !File containing restoration coefficient
[2030]55
56   !!----------------------------------------------------------------------
[2287]57   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[6613]58   !! $Id$
[2287]59   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2030]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      !!----------------------------------------------------------------------
[4147]70      INTEGER ::  ios                 ! Local integer output status for namelist read
[2030]71      NAMELIST/namtrc_adv/ ln_trcadv_cen2 , ln_trcadv_tvd   ,    &
72         &                 ln_trcadv_muscl, ln_trcadv_muscl2,    &
[3718]73         &                 ln_trcadv_ubs  , ln_trcadv_qck, ln_trcadv_msc_ups
[2030]74
[5385]75      NAMELIST/namtrc_ldf/ ln_trcldf_lap  ,     &
[2030]76         &                 ln_trcldf_bilap, ln_trcldf_level,     &
[6617]77         &                 ln_trcldf_hor  , ln_trcldf_iso  , rn_ahtrc_0, rn_ahtrb_0,   &
78         &                 rn_fact_lap
79
[2030]80      NAMELIST/namtrc_zdf/ ln_trczdf_exp  , nn_trczdf_exp
81      NAMELIST/namtrc_rad/ ln_trcrad
[5102]82      NAMELIST/namtrc_dmp/ nn_zdmp_tr , cn_resto_tr
[2030]83      !!----------------------------------------------------------------------
84
85      IF(lwp) WRITE(numout,*)
86      IF(lwp) WRITE(numout,*) ' trc_nam_trp: read namelist for tracer transport'
87      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~'
88
[4147]89      REWIND( numnat_ref )              ! Namelist namtrc_adv in reference namelist : Tracer advection scheme
90      READ  ( numnat_ref, namtrc_adv, IOSTAT = ios, ERR = 901)
91901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in reference namelist', lwp )
[2030]92
[4147]93      REWIND( numnat_cfg )              ! Namelist namtrc_adv in configuration namelist : Tracer advection scheme
94      READ  ( numnat_cfg, namtrc_adv, IOSTAT = ios, ERR = 902 )
95902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_adv in configuration namelist', lwp )
[4624]96      IF(lwm) WRITE ( numont, namtrc_adv )
[4147]97
[2030]98      IF(lwp) THEN                    ! Namelist print
99         WRITE(numout,*)
100         WRITE(numout,*) 'trc_adv_ctl : choice/control of the tracer advection scheme'
101         WRITE(numout,*) '~~~~~~~~~~~'
102         WRITE(numout,*) '   Namelist namtrc_adv : chose a advection scheme for tracers'
103         WRITE(numout,*) '      2nd order advection scheme     ln_trcadv_cen2   = ', ln_trcadv_cen2
104         WRITE(numout,*) '      TVD advection scheme           ln_trcadv_tvd    = ', ln_trcadv_tvd
105         WRITE(numout,*) '      MUSCL  advection scheme        ln_trcadv_muscl  = ', ln_trcadv_muscl
106         WRITE(numout,*) '      MUSCL2 advection scheme        ln_trcadv_muscl2 = ', ln_trcadv_muscl2
107         WRITE(numout,*) '      UBS    advection scheme        ln_trcadv_ubs    = ', ln_trcadv_ubs
108         WRITE(numout,*) '      QUICKEST advection scheme      ln_trcadv_qck    = ', ln_trcadv_qck
109      ENDIF
110      !
[4147]111      REWIND( numnat_ref )              ! Namelist namtrc_ldf in reference namelist : Tracer lateral diffusive operator
112      READ  ( numnat_ref, namtrc_ldf, IOSTAT = ios, ERR = 903)
113903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in reference namelist', lwp )
[2030]114
[4147]115      REWIND( numnat_cfg )              ! Namelist namtrc_ldf in configuration namelist : Tracer lateral diffusive operator
116      READ  ( numnat_cfg, namtrc_ldf, IOSTAT = ios, ERR = 904 )
117904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ldf in configuration namelist', lwp )
[4624]118      IF(lwm) WRITE ( numont, namtrc_ldf )
[4147]119
[2030]120      IF(lwp) THEN                    ! Namelist print
121         WRITE(numout,*)
122         WRITE(numout,*) 'trc:ldf_ctl : lateral tracer diffusive operator'
123         WRITE(numout,*) '~~~~~~~~~~~'
124         WRITE(numout,*) '   Namelist namtrc_ldf : set lateral mixing parameters (type, direction, coefficients)'
125         WRITE(numout,*) '      laplacian operator                                 ln_trcldf_lap   = ', ln_trcldf_lap
126         WRITE(numout,*) '      bilaplacian operator                               ln_trcldf_bilap = ', ln_trcldf_bilap
127         WRITE(numout,*) '      iso-level                                          ln_trcldf_level = ', ln_trcldf_level
128         WRITE(numout,*) '      horizontal (geopotential)                          ln_trcldf_hor   = ', ln_trcldf_hor
129         WRITE(numout,*) '      iso-neutral                                        ln_trcldf_iso   = ', ln_trcldf_iso
[3294]130         WRITE(numout,*) '      diffusivity coefficient                                 rn_ahtrc_0 = ', rn_ahtrc_0
[2030]131         WRITE(numout,*) '      background hor. diffusivity                             rn_ahtrb_0 = ', rn_ahtrb_0
[6617]132         WRITE(numout,*) '      enhanced zonal diffusivity                             rn_fact_lap = ', rn_fact_lap
[2030]133      ENDIF
134
135      !                                ! Vertical mixing
[4147]136      REWIND( numnat_ref )              ! Namelist namtrc_zdf in reference namelist : Tracer vertical mixing
137      READ  ( numnat_ref, namtrc_zdf, IOSTAT = ios, ERR = 905)
138905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in reference namelist', lwp )
[2030]139
[4147]140      REWIND( numnat_cfg )              ! Namelist namtrc_zdf in configuration namelist : Tracer vertical mixing
141      READ  ( numnat_cfg, namtrc_zdf, IOSTAT = ios, ERR = 906 )
142906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_zdf in configuration namelist', lwp )
[4624]143      IF(lwm) WRITE ( numont, namtrc_zdf )
[4147]144
[2030]145      IF(lwp) THEN                     !   ! Control print
146         WRITE(numout,*)
147         WRITE(numout,*) '   Namelist namtrc_zdf : set vertical diffusion parameters'
148         WRITE(numout,*) '      time splitting / backward scheme ln_trczdf_exp = ', ln_trczdf_exp
149         WRITE(numout,*) '      number of time step              nn_trczdf_exp = ', nn_trczdf_exp
150      ENDIF
151
152      !
[4147]153      REWIND( numnat_ref )              ! Namelist namtrc_rad in reference namelist : Tracer negative concentrations
154      READ  ( numnat_ref, namtrc_rad, IOSTAT = ios, ERR = 907)
155907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in reference namelist', lwp )
[2030]156
[4147]157      REWIND( numnat_cfg )              ! Namelist namtrc_rad in configuration namelist : Tracer negative concentrations
158      READ  ( numnat_cfg, namtrc_rad, IOSTAT = ios, ERR = 908 )
159908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_rad in configuration namelist', lwp )
[4624]160      IF(lwm) WRITE ( numont, namtrc_rad )
[4147]161
[2030]162      IF(lwp) THEN                     !   ! Control print
163         WRITE(numout,*)
164         WRITE(numout,*) '   Namelist namtrc_rad : treatment of negative concentrations'
165         WRITE(numout,*) '      correct artificially negative concen. or not ln_trcrad = ', ln_trcrad
166      ENDIF
167
168
[4147]169      REWIND( numnat_ref )              ! Namelist namtrc_dmp in reference namelist : Passive tracers newtonian damping
170      READ  ( numnat_ref, namtrc_dmp, IOSTAT = ios, ERR = 909)
171909   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in reference namelist', lwp )
172
173      REWIND( numnat_cfg )              ! Namelist namtrc_dmp in configuration namelist : Passive tracers newtonian damping
174      READ  ( numnat_cfg, namtrc_dmp, IOSTAT = ios, ERR = 910)
175910   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dmp in configuration namelist', lwp )
[4624]176      IF(lwm) WRITE ( numont, namtrc_dmp )
[4147]177
[2030]178      IF(lwp) THEN                       ! Namelist print
179         WRITE(numout,*)
180         WRITE(numout,*) 'trc_dmp : Passive tracers newtonian damping'
181         WRITE(numout,*) '~~~~~~~'
182         WRITE(numout,*) '   Namelist namtrc_dmp : set damping parameter'
183         WRITE(numout,*) '      mixed layer damping option     nn_zdmp_tr = ', nn_zdmp_tr, '(zoom: forced to 0)'
[5102]184         WRITE(numout,*) '      Restoration coeff file    cn_resto_tr = ', cn_resto_tr
[2030]185      ENDIF
186      !
187   END SUBROUTINE trc_nam_trp
188   
189#else
190   !!----------------------------------------------------------------------
191   !!   Dummy module :                                         No TOP model
192   !!----------------------------------------------------------------------
193CONTAINS
194   SUBROUTINE trc_nam_trp              ! Empty routine
195   END SUBROUTINE trc_nam_trp
196#endif
197
198  !!======================================================================
199END MODULE trcnam_trp
Note: See TracBrowser for help on using the repository browser.