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.F90 in NEMO/releases/r4.0/r4.0-HEAD/src/TOP – NEMO

source: NEMO/releases/r4.0/r4.0-HEAD/src/TOP/trcnam.F90 @ 15613

Last change on this file since 15613 was 15613, checked in by cetlod, 2 years ago

r4.0-HEAD : bugfix to better manage the diurnal cycle in TOP, see ticket #2739

  • Property svn:keywords set to Id
File size: 16.1 KB
Line 
1MODULE trcnam
2   !!======================================================================
3   !!                       ***  MODULE trcnam  ***
4   !! TOP :   Read and print options for the passive tracer run (namelist)
5   !!======================================================================
6   !! History :    -   !  1996-11  (M.A. Foujols, M. Levy)  original code
7   !!              -   !  1998-04  (M.A Foujols, L. Bopp) ahtrb0 for isopycnal mixing
8   !!              -   !  1999-10  (M.A. Foujols, M. Levy) separation of sms
9   !!              -   !  2000-07  (A. Estublier) add TVD and MUSCL : Tests on ndttrc
10   !!              -   !  2000-11  (M.A Foujols, E Kestenare) trcrat, ahtrc0 and aeivtr0
11   !!              -   !  2001-01 (E Kestenare) suppress ndttrc=1 for CEN2 and TVD schemes
12   !!             1.0  !  2005-03 (O. Aumont, A. El Moussaoui) F90
13   !!----------------------------------------------------------------------
14#if defined key_top
15   !!----------------------------------------------------------------------
16   !!   'key_top'                                                TOP models
17   !!----------------------------------------------------------------------
18   !!   trc_nam    :  Read and print options for the passive tracer run (namelist)
19   !!----------------------------------------------------------------------
20   USE oce_trc     ! shared variables between ocean and passive tracers
21   USE trc         ! passive tracers common variables
22   USE trd_oce     !       
23   USE trdtrc_oce  !
24   USE iom         ! I/O manager
25#if defined key_mpp_mpi
26   USE lib_mpp, ONLY: ncom_dttrc
27#endif
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   trc_nam_run  ! called in trcini
33   PUBLIC   trc_nam      ! called in trcini
34
35   TYPE(PTRACER), DIMENSION(jpmaxtrc), PUBLIC  :: sn_tracer  !: type of tracer for saving if not key_iomput
36
37   !!----------------------------------------------------------------------
38   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
39   !! $Id$
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE trc_nam
45      !!---------------------------------------------------------------------
46      !!                     ***  ROUTINE trc_nam  ***
47      !!
48      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
49      !!
50      !! ** Method  : - read passive tracer namelist
51      !!              - read namelist of each defined SMS model
52      !!                ( (PISCES, CFC, MY_TRC )
53      !!---------------------------------------------------------------------
54      INTEGER  ::   jn   ! dummy loop indice
55      !!---------------------------------------------------------------------
56      !
57      IF( .NOT.l_offline )   CALL trc_nam_run     ! Parameters of the run                                 
58      !               
59      CALL trc_nam_trc                            ! passive tracer informations
60      !                                       
61      IF( ln_rsttr                     )   ln_trcdta = .FALSE.   ! restart : no need of clim data
62      !
63      IF( ln_trcdmp .OR. ln_trcdmp_clo )   ln_trcdta = .TRUE.    ! damping : need to have clim data
64      !
65      !
66      IF(lwp) THEN                   ! control print
67         IF( ln_rsttr ) THEN
68            WRITE(numout,*)
69            WRITE(numout,*) '   ==>>>   Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
70         ENDIF
71         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
72            WRITE(numout,*)
73            WRITE(numout,*) '   ==>>>   Some of the passive tracers are initialised from climatologies '
74         ENDIF
75         IF( .NOT.ln_trcdta ) THEN
76            WRITE(numout,*)
77            WRITE(numout,*) '   ==>>>   All the passive tracers are initialised with constant values '
78         ENDIF
79      ENDIF
80      !
81      rdttrc = rdt * FLOAT( nn_dttrc )          ! passive tracer time-step     
82      !
83      IF(lwp) THEN                              ! control print
84        WRITE(numout,*) 
85        WRITE(numout,*) '   ==>>>   Passive Tracer  time step    rdttrc = nn_dttrc*rdt = ', rdttrc
86      ENDIF
87      !
88                            CALL trc_nam_opt    ! Optical
89      !
90      IF( l_trdtrc )        CALL trc_nam_trd    ! Passive tracer trends
91      !
92   END SUBROUTINE trc_nam
93
94
95   SUBROUTINE trc_nam_run
96      !!---------------------------------------------------------------------
97      !!                     ***  ROUTINE trc_nam  ***
98      !!
99      !! ** Purpose :   read options for the passive tracer run (namelist)
100      !!
101      !!---------------------------------------------------------------------
102      INTEGER  ::   ios   ! Local integer
103      !!
104      NAMELIST/namtrc_run/ nn_dttrc, ln_rsttr, nn_rsttr, ln_top_euler, &
105        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out
106      !!---------------------------------------------------------------------
107      !
108      IF(lwp) WRITE(numout,*)
109      IF(lwp) WRITE(numout,*) 'trc_nam_run : read the passive tracer namelists'
110      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
111      !
112      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
113      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
114      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 )
115      !
116      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
117      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901)
118901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist' )
119      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
120      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 )
121902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist' )
122      IF(lwm) WRITE( numont, namtrc_run )
123
124      nittrc000 = nit000 + nn_dttrc - 1      ! first time step of tracer model
125
126      IF(lwp) THEN                   ! control print
127         WRITE(numout,*) '   Namelist : namtrc_run'
128         WRITE(numout,*) '      time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
129         WRITE(numout,*) '      restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
130         WRITE(numout,*) '      control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
131         WRITE(numout,*) '      first time step for pass. trac.              nittrc000     = ', nittrc000
132         WRITE(numout,*) '      Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
133      ENDIF
134      !
135#if defined key_mpp_mpi
136      ncom_dttrc = nn_dttrc    ! make nn_fsbc available for lib_mpp
137#endif
138      !
139   END SUBROUTINE trc_nam_run
140
141
142   SUBROUTINE trc_nam_trc
143      !!---------------------------------------------------------------------
144      !!                     ***  ROUTINE trc_nam  ***
145      !!
146      !! ** Purpose :   read options for the passive tracer run (namelist)
147      !!
148      !!---------------------------------------------------------------------
149      INTEGER ::   ios, ierr, icfc       ! Local integer
150      !!
151      NAMELIST/namtrc/jp_bgc, ln_pisces, ln_my_trc, ln_age, ln_cfc11, ln_cfc12, ln_sf6, ln_c14, &
152         &            sn_tracer, ln_trcdta, ln_trcdmp, ln_trcdmp_clo, jp_dia3d, jp_dia2d
153      !!---------------------------------------------------------------------
154      ! Dummy settings to fill tracers data structure
155      !                  !   name   !   title   !   unit   !   init  !   sbc   !   cbc   !   obc  !
156      sn_tracer = PTRACER( 'NONAME' , 'NOTITLE' , 'NOUNIT' , .false. , .false. , .false. , .false.)
157      !
158      IF(lwp) WRITE(numout,*)
159      IF(lwp) WRITE(numout,*) 'trc_nam_trc : read the passive tracer namelists'
160      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
161
162      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
163      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
164901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc in reference namelist' )
165      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
166      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
167902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc in configuration namelist' )
168      IF(lwm) WRITE( numont, namtrc )
169
170      ! Control settings
171      IF( ln_pisces .AND. ln_my_trc )   CALL ctl_stop( 'Choose only ONE BGC model - PISCES or MY_TRC' )
172      IF( .NOT. ln_pisces .AND. .NOT. ln_my_trc )   jp_bgc = 0
173      ll_cfc = ln_cfc11 .OR. ln_cfc12 .OR. ln_sf6
174      !
175      jptra       =  0
176      jp_pisces   =  0    ;   jp_pcs0  =  0    ;   jp_pcs1  = 0
177      jp_my_trc   =  0    ;   jp_myt0  =  0    ;   jp_myt1  = 0
178      jp_cfc      =  0    ;   jp_cfc0  =  0    ;   jp_cfc1  = 0
179      jp_age      =  0    ;   jp_c14   =  0
180      !
181      IF( ln_pisces )  THEN
182         jp_pisces = jp_bgc
183         jp_pcs0   = 1
184         jp_pcs1   = jp_pisces
185      ENDIF
186      IF( ln_my_trc )  THEN
187          jp_my_trc = jp_bgc
188          jp_myt0   = 1
189          jp_myt1   = jp_my_trc
190      ENDIF
191      !
192      jptra  = jp_bgc
193      !
194      IF( ln_age )    THEN
195         jptra     = jptra + 1
196         jp_age    = jptra
197      ENDIF
198      IF( ln_cfc11 )  jp_cfc = jp_cfc + 1
199      IF( ln_cfc12 )  jp_cfc = jp_cfc + 1
200      IF( ln_sf6   )  jp_cfc = jp_cfc + 1
201      IF( ll_cfc )    THEN
202          jptra     = jptra + jp_cfc
203          jp_cfc0   = jptra - jp_cfc + 1
204          jp_cfc1   = jptra
205      ENDIF
206      IF( ln_c14 )    THEN
207           jptra     = jptra + 1
208           jp_c14    = jptra
209      ENDIF
210      !
211      IF( jptra == 0 )   CALL ctl_stop( 'All TOP tracers disabled: change namtrc setting or check if key_top is active' )
212      !
213      IF(lwp) THEN                   ! control print
214         WRITE(numout,*) '   Namelist : namtrc'
215         WRITE(numout,*) '      Total number of passive tracers              jptra         = ', jptra
216         WRITE(numout,*) '      Total number of BGC tracers                  jp_bgc        = ', jp_bgc
217         WRITE(numout,*) '      Simulating PISCES model                      ln_pisces     = ', ln_pisces
218         WRITE(numout,*) '      Simulating MY_TRC  model                     ln_my_trc     = ', ln_my_trc
219         WRITE(numout,*) '      Simulating water mass age                    ln_age        = ', ln_age
220         WRITE(numout,*) '      Simulating CFC11 passive tracer              ln_cfc11      = ', ln_cfc11
221         WRITE(numout,*) '      Simulating CFC12 passive tracer              ln_cfc12      = ', ln_cfc12
222         WRITE(numout,*) '      Simulating SF6 passive tracer                ln_sf6        = ', ln_sf6
223         WRITE(numout,*) '      Total number of CFCs tracers                 jp_cfc        = ', jp_cfc
224         WRITE(numout,*) '      Simulating C14   passive tracer              ln_c14        = ', ln_c14
225         WRITE(numout,*) '      Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
226         WRITE(numout,*) '      Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
227         WRITE(numout,*) '      Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
228      ENDIF
229      !
230      IF( ll_cfc .OR. ln_c14 ) THEN
231        !                             ! Open namelist files
232        CALL ctl_opn( numtrc_ref, 'namelist_trc_ref'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
233        CALL ctl_opn( numtrc_cfg, 'namelist_trc_cfg'   ,     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
234        IF(lwm) CALL ctl_opn( numonr, 'output.namelist.trc', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
235        !
236      ENDIF
237      !
238   END SUBROUTINE trc_nam_trc
239
240   SUBROUTINE trc_nam_opt
241      !!---------------------------------------------------------------------
242      !!                     ***  ROUTINE trc_nam_opt  ***
243      !!
244      !! ** Purpose :   read options for the passive tracer diagnostics
245      !!
246      !!---------------------------------------------------------------------
247      INTEGER  ::   ios, ierr                 ! Local integer
248      !!
249      NAMELIST/namtrc_opt/ ln_trcdc2dm
250      !!---------------------------------------------------------------------
251      !
252      IF(lwp) WRITE(numout,*)
253      IF(lwp) WRITE(numout,*) 'trc_nam_opt : read the passive tracer optical options'
254      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
255      !
256      !
257      REWIND( numnat_ref )              ! Namelist namtrc_opt in reference namelist : Passive tracer trends
258      READ  ( numnat_ref, namtrc_opt, IOSTAT = ios, ERR = 905)
259905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_opt in reference namelist' )
260      REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
261      READ  ( numnat_cfg, namtrc_opt, IOSTAT = ios, ERR = 906 )
262906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_opt in configuration namelist' )
263      IF(lwm) WRITE( numont, namtrc_opt )
264
265      IF(lwp) THEN
266         WRITE(numout,*) '   Namelist : namtrc_opt                    '
267         WRITE(numout,*) '      Diurnal cycle for TOP ln_trcdc2dm    = ', ln_trcdc2dm
268      ENDIF
269
270   END SUBROUTINE trc_nam_opt
271
272
273   SUBROUTINE trc_nam_trd
274      !!---------------------------------------------------------------------
275      !!                     ***  ROUTINE trc_nam_dia  ***
276      !!
277      !! ** Purpose :   read options for the passive tracer diagnostics
278      !!
279      !! ** Method  : - read passive tracer namelist
280      !!              - read namelist of each defined SMS model
281      !!                ( (PISCES, CFC, MY_TRC )
282      !!---------------------------------------------------------------------
283#if defined key_trdmxl_trc  || defined key_trdtrc
284      INTEGER  ::   ios, ierr                 ! Local integer
285      !!
286      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
287         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, &
288         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
289      !!---------------------------------------------------------------------
290      !
291      IF(lwp) WRITE(numout,*)
292      IF(lwp) WRITE(numout,*) 'trc_nam_trd : read the passive tracer diagnostics options'
293      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~'
294      !
295      ALLOCATE( ln_trdtrc(jptra) ) 
296      !
297      REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
298      READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
299905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtrc_trd in reference namelist' )
300      REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
301      READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
302906   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist' )
303      IF(lwm) WRITE( numont, namtrc_trd )
304
305      IF(lwp) THEN
306         WRITE(numout,*) '   Namelist : namtrc_trd                    '
307         WRITE(numout,*) '      frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
308         WRITE(numout,*) '      control surface type              nn_ctls_trc            = ', nn_ctls_trc
309         WRITE(numout,*) '      restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart
310         WRITE(numout,*) '      instantantaneous or mean trends   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant
311         WRITE(numout,*) '      unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
312         DO jn = 1, jptra
313            IF( ln_trdtrc(jn) ) WRITE(numout,*) '      compute ML trends for tracer number :', jn
314         END DO
315      ENDIF
316#endif
317      !
318   END SUBROUTINE trc_nam_trd
319
320#else
321   !!----------------------------------------------------------------------
322   !!  Dummy module :                                     No passive tracer
323   !!----------------------------------------------------------------------
324CONTAINS
325   SUBROUTINE trc_nam                      ! Empty routine   
326   END SUBROUTINE trc_nam
327   SUBROUTINE trc_nam_run                      ! Empty routine   
328   END SUBROUTINE trc_nam_run
329#endif
330
331   !!======================================================================
332END MODULE trcnam
Note: See TracBrowser for help on using the repository browser.