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 branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 @ 7873

Last change on this file since 7873 was 7873, checked in by cetlod, 7 years ago

v3.6stable: minor corrections to avoid compilation errors when using 3D trends diagnostics in TOP

  • Property svn:keywords set to Id
File size: 18.3 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 trcnam_trp        ! Transport namelist
23   USE trcnam_pisces     ! PISCES namelist
24   USE trcnam_cfc        ! CFC SMS namelist
25   USE trcnam_c14b       ! C14 SMS namelist
26   USE trcnam_age        ! AGE SMS namelist
27   USE trcnam_my_trc     ! MY_TRC SMS namelist
28   USE trd_oce       
29   USE trdtrc_oce
30   USE iom               ! I/O manager
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC trc_nam_run  ! called in trcini
36   PUBLIC trc_nam      ! called in trcini
37
38   !! * Substitutions
39#  include "top_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
42   !! $Id$
43   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45
46CONTAINS
47
48
49   SUBROUTINE trc_nam
50      !!---------------------------------------------------------------------
51      !!                     ***  ROUTINE trc_nam  ***
52      !!
53      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
54      !!
55      !! ** Method  : - read passive tracer namelist
56      !!              - read namelist of each defined SMS model
57      !!                ( (PISCES, CFC, MY_TRC )
58      !!---------------------------------------------------------------------
59      INTEGER  ::   jn                  ! dummy loop indice
60      !                                        !   Parameters of the run
61      IF( .NOT. lk_offline ) CALL trc_nam_run
62     
63      !                                        !  passive tracer informations
64                             CALL trc_nam_trc
65     
66      !                                        !   Parameters of additional diagnostics
67      IF( .NOT. lk_iomput)   CALL trc_nam_dia
68
69      !                                        !   namelist of transport
70                             CALL trc_nam_trp
71
72
73      IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data
74      !
75      IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data
76      !
77      IF( .NOT.ln_trcdta ) THEN
78         ln_trc_ini(:) = .FALSE.
79      ENDIF
80
81     IF(lwp) THEN                   ! control print
82         WRITE(numout,*)
83         WRITE(numout,*) ' Namelist : namtrc'
84         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
85         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
86         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
87         WRITE(numout,*) ' '
88         DO jn = 1, jptra
89            WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn)
90         END DO
91         WRITE(numout,*) ' '
92      ENDIF
93
94      IF(lwp) THEN                   ! control print
95         IF( ln_rsttr ) THEN
96            WRITE(numout,*)
97            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
98            WRITE(numout,*)
99         ENDIF
100         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
101            WRITE(numout,*)
102            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies '
103            WRITE(numout,*)
104         ENDIF
105         IF( .NOT.ln_trcdta ) THEN
106            WRITE(numout,*)
107            WRITE(numout,*) '  All the passive tracers are initialised with constant values '
108            WRITE(numout,*)
109         ENDIF
110      ENDIF
111
112     
113      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step
114 
115      IF(lwp) THEN                   ! control print
116        WRITE(numout,*) 
117        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1)
118        WRITE(numout,*) 
119      ENDIF
120
121
122      ! Call the ice module for tracers
123      ! -------------------------------
124      CALL trc_nam_ice
125
126      ! namelist of SMS
127      ! ---------------     
128      IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model
129      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used'
130      ENDIF
131
132      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers
133      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used'
134      ENDIF
135
136      IF( lk_c14b    ) THEN  ;   CALL trc_nam_c14b         ! C14 bomb     tracers
137      ELSE                   ;   IF(lwp) WRITE(numout,*) '          C14 not used'
138      ENDIF
139
140      IF( lk_age     ) THEN  ;   CALL trc_nam_age         ! AGE     tracer
141      ELSE                   ;   IF(lwp) WRITE(numout,*) '          AGE not used'
142      ENDIF
143
144      IF( lk_my_trc  ) THEN  ;   CALL trc_nam_my_trc      ! MY_TRC  tracers
145      ELSE                   ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used'
146      ENDIF
147      !
148   END SUBROUTINE trc_nam
149
150   SUBROUTINE trc_nam_run
151      !!---------------------------------------------------------------------
152      !!                     ***  ROUTINE trc_nam  ***
153      !!
154      !! ** Purpose :   read options for the passive tracer run (namelist)
155      !!
156      !!---------------------------------------------------------------------
157      NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, &
158        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out
159
160
161      INTEGER  ::   ios                 ! Local integer output status for namelist read
162
163      !!---------------------------------------------------------------------
164
165
166      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
167      IF(lwp) WRITE(numout,*) '~~~~~~~'
168
169      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
170      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
171      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 )
172
173      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
174      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901)
175901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
176
177      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
178      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 )
179902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
180      IF(lwm) WRITE ( numont, namtrc_run )
181
182      !  computes the first time step of tracer model
183      nittrc000 = nit000 + nn_dttrc - 1
184
185      IF(lwp) THEN                   ! control print
186         WRITE(numout,*)
187         WRITE(numout,*) ' Namelist : namtrc_run'
188         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
189         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
190         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
191         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000
192         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc 
193         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
194         WRITE(numout,*) ' '
195      ENDIF
196      !
197    END SUBROUTINE trc_nam_run
198
199   SUBROUTINE trc_nam_ice
200      !!---------------------------------------------------------------------
201      !!                     ***  ROUTINE trc_nam_ice ***
202      !!
203      !! ** Purpose :   Read the namelist for the ice effect on tracers
204      !!
205      !! ** Method  : -
206      !!
207      !!---------------------------------------------------------------------
208      ! --- Variable declarations --- !
209      INTEGER :: jn      ! dummy loop indices
210      INTEGER :: ios     ! Local integer output status for namelist read
211
212      ! --- Namelist declarations --- !
213      TYPE(TRC_I_NML), DIMENSION(jptra) :: sn_tri_tracer
214      NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer
215
216      IF(lwp) THEN
217         WRITE(numout,*)
218         WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice'
219         WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
220      ENDIF
221
222      IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice')
223
224      !
225      REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data
226      READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901)
227 901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp )
228
229      REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients
230      READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 )
231 902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp )
232
233      IF( lwp ) THEN
234         WRITE(numout,*) ' '
235         WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr
236         WRITE(numout,*) ' '
237      ENDIF
238
239      ! Assign namelist stuff
240      DO jn = 1, jptra
241         trc_ice_ratio(jn)  = sn_tri_tracer(jn)%trc_ratio
242         trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr
243         cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o
244      END DO
245
246      IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice')
247      !
248   END SUBROUTINE trc_nam_ice
249
250   SUBROUTINE trc_nam_trc
251      !!---------------------------------------------------------------------
252      !!                     ***  ROUTINE trc_nam  ***
253      !!
254      !! ** Purpose :   read options for the passive tracer run (namelist)
255      !!
256      !!---------------------------------------------------------------------
257      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput
258      !!
259      NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo
260 
261      INTEGER  ::   ios                 ! Local integer output status for namelist read
262      INTEGER  ::   jn                  ! dummy loop indice
263      !!---------------------------------------------------------------------
264      IF(lwp) WRITE(numout,*)
265      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
266      IF(lwp) WRITE(numout,*) '~~~~~~~'
267
268
269      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
270      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
271901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
272
273      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
274      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
275902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
276      IF(lwm) WRITE ( numont, namtrc )
277
278      DO jn = 1, jptra
279         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname )
280         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname )
281         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  )
282         ln_trc_ini(jn) =       sn_tracer(jn)%llinit
283         ln_trc_wri(jn) =       sn_tracer(jn)%llsave
284      END DO
285     
286    END SUBROUTINE trc_nam_trc
287
288
289   SUBROUTINE trc_nam_dia
290      !!---------------------------------------------------------------------
291      !!                     ***  ROUTINE trc_nam_dia  ***
292      !!
293      !! ** Purpose :   read options for the passive tracer diagnostics
294      !!
295      !! ** Method  : - read passive tracer namelist
296      !!              - read namelist of each defined SMS model
297      !!                ( (PISCES, CFC, MY_TRC )
298      !!---------------------------------------------------------------------
299      INTEGER ::  ierr
300#if defined key_trdmxl_trc  || defined key_trdtrc
301      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
302         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, &
303         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
304#endif
305      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio
306
307      INTEGER  ::   jn       
308      INTEGER  ::   ios                 ! Local integer output status for namelist read
309      !!---------------------------------------------------------------------
310
311      IF(lwp) WRITE(numout,*) 
312      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
313      IF(lwp) WRITE(numout,*) '~~~~~~~'
314
315      IF(lwp) WRITE(numout,*)
316      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
317      IF(lwp) WRITE(numout,*) '~~~~~~~'
318
319      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics
320      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903)
321903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp )
322
323      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics
324      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 )
325904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp )
326      IF(lwm) WRITE ( numont, namtrc_dia )
327
328      IF(lwp) THEN
329         WRITE(numout,*)
330         WRITE(numout,*)
331         WRITE(numout,*) ' Namelist : namtrc_dia'
332         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc
333         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio
334         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia
335         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio
336         WRITE(numout,*) ' '
337      ENDIF
338
339      IF( ln_diatrc ) THEN
340         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  &
341           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  & 
342           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr ) 
343         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' )
344         !
345         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' ' 
346         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' ' 
347         !
348      ENDIF
349
350      IF( ln_diabio .OR. l_trdtrc ) THEN
351         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , &
352           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr ) 
353         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' )
354         !
355         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' ' 
356         !
357      ENDIF
358
359#if defined key_trdmxl_trc || defined key_trdtrc
360
361         REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
362         READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
363905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp )
364
365         REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
366         READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
367906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp )
368         IF(lwm) WRITE ( numont, namtrc_trd )
369
370         IF(lwp) THEN
371            WRITE(numout,*)
372            WRITE(numout,*) ' trd_mxl_trc_init : read namelist namtrc_trd                    '
373            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               '
374            WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
375            WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc
376            WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart
377            WRITE(numout,*) '   * flag to diagnose trends of                                 '
378            WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant
379            WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
380            DO jn = 1, jptra
381               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn
382            END DO
383         ENDIF
384#endif
385      !
386   END SUBROUTINE trc_nam_dia
387
388#else
389   !!----------------------------------------------------------------------
390   !!  Dummy module :                                     No passive tracer
391   !!----------------------------------------------------------------------
392CONTAINS
393   SUBROUTINE trc_nam                      ! Empty routine   
394   END SUBROUTINE trc_nam
395   SUBROUTINE trc_nam_run                      ! Empty routine   
396   END SUBROUTINE trc_nam_run
397#endif
398
399   !!----------------------------------------------------------------------
400   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
401   !! $Id$
402   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
403   !!======================================================================
404END MODULE trcnam
Note: See TracBrowser for help on using the repository browser.