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/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/trcnam.F90 @ 6715

Last change on this file since 6715 was 6715, checked in by jpalmier, 8 years ago

JPALM -- 16-06-2016 -- MEDUSA branch update :

-- pass co2 flux and dms_surf through restart for atm coupling.
-- introduce CFC cycle for dynamic evolution comparison
-- add Tim Graham Age tracer
-- include MEDUSA Q10 modif
-- svn-key removed
-- still need debug stage

File size: 23.8 KB
RevLine 
[2038]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
[5841]13   !!              -   !  2014-06  (A. Yool, J. Palmieri) adding MEDUSA-2
[2038]14   !!----------------------------------------------------------------------
15#if defined key_top
16   !!----------------------------------------------------------------------
17   !!   'key_top'                                                TOP models
18   !!----------------------------------------------------------------------
19   !!   trc_nam    :  Read and print options for the passive tracer run (namelist)
20   !!----------------------------------------------------------------------
[3294]21   USE oce_trc           ! shared variables between ocean and passive tracers
22   USE trc               ! passive tracers common variables
[2038]23   USE trcnam_trp        ! Transport namelist
24   USE trcnam_pisces     ! PISCES namelist
25   USE trcnam_cfc        ! CFC SMS namelist
26   USE trcnam_c14b       ! C14 SMS namelist
27   USE trcnam_my_trc     ! MY_TRC SMS namelist
[5726]28   USE trcnam_medusa     ! MEDUSA namelist
29   USE trcnam_idtra      ! Idealise tracer namelist
[6715]30   USE trcnam_age        ! AGE SMS namelist
[4990]31   USE trd_oce       
32   USE trdtrc_oce
[3294]33   USE iom               ! I/O manager
[2038]34
35   IMPLICIT NONE
36   PRIVATE
37
[4152]38   PUBLIC trc_nam_run  ! called in trcini
[2038]39   PUBLIC trc_nam      ! called in trcini
40
41   !! * Substitutions
42#  include "top_substitute.h90"
43   !!----------------------------------------------------------------------
[2287]44   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[5341]45   !! $Id$
[2287]46   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2038]47   !!----------------------------------------------------------------------
48
49CONTAINS
50
[4152]51
[2038]52   SUBROUTINE trc_nam
53      !!---------------------------------------------------------------------
54      !!                     ***  ROUTINE trc_nam  ***
55      !!
56      !! ** Purpose :   READ and PRINT options for the passive tracer run (namelist)
57      !!
58      !! ** Method  : - read passive tracer namelist
59      !!              - read namelist of each defined SMS model
[6715]60      !!                ( (PISCES, CFC, MY_TRC, MEDUSA, IDTRA, Age )
[2038]61      !!---------------------------------------------------------------------
[5726]62      INTEGER  ::   jn, jk                     ! dummy loop indice
[4152]63      !                                        !   Parameters of the run
64      IF( .NOT. lk_offline ) CALL trc_nam_run
65     
66      !                                        !  passive tracer informations
[5726]67# if defined key_debug_medusa
68      CALL flush(numout)
69      IF (lwp) write (numout,*) '------------------------------'
70      IF (lwp) write (numout,*) 'Jpalm - debug'
71      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_trc'
72      IF (lwp) write (numout,*) ' '
73# endif
74      !
[4152]75      CALL trc_nam_trc
76     
77      !                                        !   Parameters of additional diagnostics
[5726]78# if defined key_debug_medusa
79      CALL flush(numout)
80      IF (lwp) write (numout,*) '------------------------------'
81      IF (lwp) write (numout,*) 'Jpalm - debug'
82      IF (lwp) write (numout,*) 'CALL trc_nam_trc -- OK'
83      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_dia'
84      IF (lwp) write (numout,*) ' '
85# endif
86      !
87
[4152]88      CALL trc_nam_dia
[2038]89
[4152]90      !                                        !   namelist of transport
[5726]91# if defined key_debug_medusa
92      CALL flush(numout)
93      IF (lwp) write (numout,*) '------------------------------'
94      IF (lwp) write (numout,*) 'Jpalm - debug'
95      IF (lwp) write (numout,*) 'CALL trc_nam_dia -- OK'
96      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_trp'
97      IF (lwp) write (numout,*) ' '
98# endif
99      !
[4152]100      CALL trc_nam_trp
[5726]101      !
102# if defined key_debug_medusa
103      CALL flush(numout)
104      IF (lwp) write (numout,*) '------------------------------'
105      IF (lwp) write (numout,*) 'Jpalm - debug'
106      IF (lwp) write (numout,*) 'CALL trc_nam_trp -- OK'
107      IF (lwp) write (numout,*) 'continue trc_nam '
108      IF (lwp) write (numout,*) ' '
109      CALL flush(numout)
110# endif
111      !
[2038]112
113
[4152]114      IF( ln_rsttr )                      ln_trcdta = .FALSE.   ! restart : no need of clim data
115      !
116      IF( ln_trcdmp .OR. ln_trcdmp_clo )  ln_trcdta = .TRUE.   ! damping : need to have clim data
117      !
118      IF( .NOT.ln_trcdta ) THEN
119         ln_trc_ini(:) = .FALSE.
120      ENDIF
[2038]121
[4152]122     IF(lwp) THEN                   ! control print
[2038]123         WRITE(numout,*)
124         WRITE(numout,*) ' Namelist : namtrc'
[3319]125         WRITE(numout,*) '   Read inputs data from file (y/n)             ln_trcdta     = ', ln_trcdta
126         WRITE(numout,*) '   Damping of passive tracer (y/n)              ln_trcdmp     = ', ln_trcdmp
[4148]127         WRITE(numout,*) '   Restoring of tracer on closed seas           ln_trcdmp_clo = ', ln_trcdmp_clo
[2038]128         WRITE(numout,*) ' '
129         DO jn = 1, jptra
[3294]130            WRITE(numout,*) '  tracer nb : ', jn, '    short name : ', ctrcnm(jn)
[2038]131         END DO
[3294]132         WRITE(numout,*) ' '
[5726]133# if defined key_debug_medusa
134      CALL flush(numout)
135# endif
[2038]136      ENDIF
137
[3294]138      IF(lwp) THEN                   ! control print
139         IF( ln_rsttr ) THEN
140            WRITE(numout,*)
[4148]141            WRITE(numout,*) '  Read a restart file for passive tracer : ', TRIM( cn_trcrst_in )
[3294]142            WRITE(numout,*)
143         ENDIF
[4148]144         IF( ln_trcdta .AND. .NOT.ln_rsttr ) THEN
145            WRITE(numout,*)
146            WRITE(numout,*) '  Some of the passive tracers are initialised from climatologies '
147            WRITE(numout,*)
148         ENDIF
149         IF( .NOT.ln_trcdta ) THEN
150            WRITE(numout,*)
151            WRITE(numout,*) '  All the passive tracers are initialised with constant values '
152            WRITE(numout,*)
153         ENDIF
[5726]154# if defined key_debug_medusa
155      CALL flush(numout)
156# endif
[3294]157      ENDIF
158
[5726]159# if defined key_debug_medusa
160       DO jk = 1, jpk
161          WRITE(numout,*) '  level number: ', jk, 'rdttrc: ',rdttrc(jk),'rdttra: ', rdttra(jk),'nn_dttrc: ', nn_dttrc
162       END DO
163      CALL flush(numout)
164# endif
[4152]165     
166      rdttrc(:) = rdttra(:) * FLOAT( nn_dttrc )   ! vertical profile of passive tracer time-step
167 
168      IF(lwp) THEN                   ! control print
169        WRITE(numout,*) 
170        WRITE(numout,*) '    Passive Tracer  time step    rdttrc  = ', rdttrc(1)
171        WRITE(numout,*) 
[5726]172# if defined key_debug_medusa
173      CALL flush(numout)
174# endif
[4152]175      ENDIF
[3294]176
[4152]177
[4990]178#if defined key_trdmxl_trc || defined key_trdtrc
[3294]179
[4147]180         REWIND( numnat_ref )              ! Namelist namtrc_trd in reference namelist : Passive tracer trends
181         READ  ( numnat_ref, namtrc_trd, IOSTAT = ios, ERR = 905)
182905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in reference namelist', lwp )
[3294]183
[4147]184         REWIND( numnat_cfg )              ! Namelist namtrc_trd in configuration namelist : Passive tracer trends
185         READ  ( numnat_cfg, namtrc_trd, IOSTAT = ios, ERR = 906 )
186906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_trd in configuration namelist', lwp )
[4624]187         IF(lwm) WRITE ( numont, namtrc_trd )
[4147]188
[3294]189         IF(lwp) THEN
190            WRITE(numout,*)
[4990]191            WRITE(numout,*) ' trd_mxl_trc_init : read namelist namtrc_trd                    '
[3294]192            WRITE(numout,*) ' ~~~~~~~~~~~~~~~~                                               '
193            WRITE(numout,*) '   * frequency of trends diagnostics   nn_trd_trc             = ', nn_trd_trc
194            WRITE(numout,*) '   * control surface type              nn_ctls_trc            = ', nn_ctls_trc
[4990]195            WRITE(numout,*) '   * restart for ML diagnostics        ln_trdmxl_trc_restart  = ', ln_trdmxl_trc_restart
[3294]196            WRITE(numout,*) '   * flag to diagnose trends of                                 '
[4990]197            WRITE(numout,*) '     instantantaneous or mean ML T/S   ln_trdmxl_trc_instant  = ', ln_trdmxl_trc_instant
[3294]198            WRITE(numout,*) '   * unit conversion factor            rn_ucf_trc             = ', rn_ucf_trc
199            DO jn = 1, jptra
200               IF( ln_trdtrc(jn) ) WRITE(numout,*) '    compute ML trends for tracer number :', jn
201            END DO
[5726]202         WRITE(numout,*) ' '
203         CALL flush(numout)
[3294]204         ENDIF
205#endif
206
[5726]207# if defined key_debug_medusa
208      CALL flush(numout)
209      IF (lwp) write (numout,*) '------------------------------'
210      IF (lwp) write (numout,*) 'Jpalm - debug'
211      IF (lwp) write (numout,*) 'just before ice module for tracers call : '
212      IF (lwp) write (numout,*) ' '
213# endif
214      !
[3294]215
[5385]216      ! Call the ice module for tracers
217      ! -------------------------------
218      CALL trc_nam_ice
219
[5726]220# if defined key_debug_medusa
221      CALL flush(numout)
222      IF (lwp) write (numout,*) '------------------------------'
223      IF (lwp) write (numout,*) 'Jpalm - debug'
224      IF (lwp) write (numout,*) 'Will now read SMS namelists : '
225      IF (lwp) write (numout,*) ' '
226# endif
227      !
228
[2038]229      ! namelist of SMS
230      ! ---------------     
231      IF( lk_pisces  ) THEN   ;   CALL trc_nam_pisces      ! PISCES  bio-model
232      ELSE                    ;   IF(lwp) WRITE(numout,*) '          PISCES not used'
233      ENDIF
[5726]234      !
235# if defined key_debug_medusa
236      CALL flush(numout)
237      IF (lwp) write (numout,*) '------------------------------'
238      IF (lwp) write (numout,*) 'Jpalm - debug'
[6164]239      IF (lwp) write (numout,*) 'CALL trc_nam_pisces  -- OK'
[5726]240      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_medusa'
241      IF (lwp) write (numout,*) ' '
242# endif
243      !
244      IF( lk_medusa  ) THEN   ;   CALL trc_nam_medusa      ! MEDUSA  tracers
245      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MEDUSA not used'
246      ENDIF
247      !
248# if defined key_debug_medusa
249      CALL flush(numout)
250      IF (lwp) write (numout,*) '------------------------------'
251      IF (lwp) write (numout,*) 'Jpalm - debug'
252      IF (lwp) write (numout,*) 'CALL trc_nam_medusa -- OK'
253      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_idtra'
254      IF (lwp) write (numout,*) ' '
255# endif
256      !
257      IF( lk_idtra   ) THEN   ;   CALL trc_nam_idtra       ! Idealize tracers
258      ELSE                    ;   IF(lwp) WRITE(numout,*) '          Idealize tracers not used'
259      ENDIF
260      !
261# if defined key_debug_medusa
262      CALL flush(numout)
263      IF (lwp) write (numout,*) '------------------------------'
264      IF (lwp) write (numout,*) 'Jpalm - debug'
265      IF (lwp) write (numout,*) 'CALL trc_nam_idtra -- OK'
[6164]266      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_cfc'
[5726]267      IF (lwp) write (numout,*) ' '
268# endif
269      !
[6164]270      IF( lk_cfc     ) THEN   ;   CALL trc_nam_cfc         ! CFC     tracers
271      ELSE                    ;   IF(lwp) WRITE(numout,*) '          CFC not used'
272      ENDIF
[6201]273      !
274# if defined key_debug_medusa
275      CALL flush(numout)
276      IF (lwp) write (numout,*) '------------------------------'
277      IF (lwp) write (numout,*) 'Jpalm - debug'
278      IF (lwp) write (numout,*) 'CALL trc_nam_cfc -- OK'
[6715]279      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_c14'
[6201]280      IF (lwp) write (numout,*) ' '
281# endif
282      !
[6164]283      IF( lk_c14b     ) THEN   ;   CALL trc_nam_c14b         ! C14 bomb     tracers
284      ELSE                    ;   IF(lwp) WRITE(numout,*) '          C14 not used'
285      ENDIF
[6715]286      !
287# if defined key_debug_medusa
288      CALL flush(numout)
289      IF (lwp) write (numout,*) '------------------------------'
290      IF (lwp) write (numout,*) 'Jpalm - debug'
291      IF (lwp) write (numout,*) 'CALL trc_nam_c14 -- OK'
292      IF (lwp) write (numout,*) 'in trc_nam - just before CALL trc_nam_age'
293      IF (lwp) write (numout,*) ' '
294# endif
295      !
296      IF( lk_age     ) THEN  ;   CALL trc_nam_age         ! AGE     tracer
297      ELSE                   ;   IF(lwp) WRITE(numout,*) '          AGE not used'
298      ENDIF
299      !
300# if defined key_debug_medusa
301      CALL flush(numout)
302      IF (lwp) write (numout,*) '------------------------------'
303      IF (lwp) write (numout,*) 'Jpalm - debug'
304      IF (lwp) write (numout,*) 'CALL trc_nam_age -- OK'
305      IF (lwp) write (numout,*) 'in trc_nam - CALL trc_nam -- OK'
306      IF (lwp) write (numout,*) ' '
307# endif
308      !
[6164]309      IF( lk_my_trc  ) THEN   ;   CALL trc_nam_my_trc      ! MY_TRC  tracers
310      ELSE                    ;   IF(lwp) WRITE(numout,*) '          MY_TRC not used'
311      ENDIF
312       
[5726]313      IF(lwp)   CALL flush(numout)
[2038]314   END SUBROUTINE trc_nam
315
[4152]316   SUBROUTINE trc_nam_run
317      !!---------------------------------------------------------------------
318      !!                     ***  ROUTINE trc_nam  ***
319      !!
320      !! ** Purpose :   read options for the passive tracer run (namelist)
321      !!
322      !!---------------------------------------------------------------------
323      NAMELIST/namtrc_run/ nn_dttrc, nn_writetrc, ln_rsttr, nn_rsttr, ln_top_euler, &
[5341]324        &                  cn_trcrst_indir, cn_trcrst_outdir, cn_trcrst_in, cn_trcrst_out
[4152]325
[5341]326
[4154]327      INTEGER  ::   ios                 ! Local integer output status for namelist read
328
[4152]329      !!---------------------------------------------------------------------
330
331
332      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
333      IF(lwp) WRITE(numout,*) '~~~~~~~'
334
[4290]335      CALL ctl_opn( numnat_ref, 'namelist_top_ref'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
336      CALL ctl_opn( numnat_cfg, 'namelist_top_cfg'   , 'OLD'    , 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
[4624]337      IF(lwm) CALL ctl_opn( numont, 'output.namelist.top', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE., 1 )
[4152]338
339      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
340      READ  ( numnat_ref, namtrc_run, IOSTAT = ios, ERR = 901)
341901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
342
343      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
344      READ  ( numnat_cfg, namtrc_run, IOSTAT = ios, ERR = 902 )
345902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
[4624]346      IF(lwm) WRITE ( numont, namtrc_run )
[4152]347
348      !  computes the first time step of tracer model
349      nittrc000 = nit000 + nn_dttrc - 1
350
351      IF(lwp) THEN                   ! control print
352         WRITE(numout,*)
[4159]353         WRITE(numout,*) ' Namelist : namtrc_run'
[4152]354         WRITE(numout,*) '   time step freq. for passive tracer           nn_dttrc      = ', nn_dttrc
355         WRITE(numout,*) '   restart  for passive tracer                  ln_rsttr      = ', ln_rsttr
356         WRITE(numout,*) '   control of time step for passive tracer      nn_rsttr      = ', nn_rsttr
357         WRITE(numout,*) '   first time step for pass. trac.              nittrc000     = ', nittrc000
[4159]358         WRITE(numout,*) '   frequency of outputs for passive tracers     nn_writetrc   = ', nn_writetrc 
359         WRITE(numout,*) '   Use euler integration for TRC (y/n)          ln_top_euler  = ', ln_top_euler
[4152]360         WRITE(numout,*) ' '
[5726]361        CALL flush(numout)
[4152]362      ENDIF
363      !
364    END SUBROUTINE trc_nam_run
365
[5385]366   SUBROUTINE trc_nam_ice
367      !!---------------------------------------------------------------------
368      !!                     ***  ROUTINE trc_nam_ice ***
369      !!
370      !! ** Purpose :   Read the namelist for the ice effect on tracers
371      !!
372      !! ** Method  : -
373      !!
374      !!---------------------------------------------------------------------
375      ! --- Variable declarations --- !
376      INTEGER :: jn      ! dummy loop indices
377      INTEGER :: ios     ! Local integer output status for namelist read
[4152]378
[5385]379      ! --- Namelist declarations --- !
380      TYPE(TRC_I_NML), DIMENSION(jptra) :: sn_tri_tracer
381      NAMELIST/namtrc_ice/ nn_ice_tr, sn_tri_tracer
382
383      IF(lwp) THEN
384         WRITE(numout,*)
385         WRITE(numout,*) 'trc_nam_ice : Read the namelist for trc_ice'
386         WRITE(numout,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
387      ENDIF
388
389      IF( nn_timing == 1 )  CALL timing_start('trc_nam_ice')
390
391      !
392      REWIND( numnat_ref )              ! Namelist namtrc_ice in reference namelist : Passive tracer input data
393      READ  ( numnat_ref, namtrc_ice, IOSTAT = ios, ERR = 901)
394 901  IF( ios /= 0 ) CALL ctl_nam ( ios , ' namtrc_ice in reference namelist ', lwp )
395
396      REWIND( numnat_cfg )              ! Namelist namtrc_ice in configuration namelist : Pisces external sources of nutrients
397      READ  ( numnat_cfg, namtrc_ice, IOSTAT = ios, ERR = 902 )
398 902  IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_ice in configuration namelist', lwp )
399
[5411]400      IF( lwp ) THEN
401         WRITE(numout,*) ' '
402         WRITE(numout,*) ' Sea ice tracers option (nn_ice_tr) : ', nn_ice_tr
403         WRITE(numout,*) ' '
404      ENDIF
[5385]405
406      ! Assign namelist stuff
407      DO jn = 1, jptra
408         trc_ice_ratio(jn)  = sn_tri_tracer(jn)%trc_ratio
409         trc_ice_prescr(jn) = sn_tri_tracer(jn)%trc_prescr
410         cn_trc_o      (jn) = sn_tri_tracer(jn)%ctrc_o
411      END DO
412
413      IF( nn_timing == 1 )   CALL timing_stop('trc_nam_ice')
414      !
415   END SUBROUTINE trc_nam_ice
416
[4152]417   SUBROUTINE trc_nam_trc
418      !!---------------------------------------------------------------------
419      !!                     ***  ROUTINE trc_nam  ***
420      !!
421      !! ** Purpose :   read options for the passive tracer run (namelist)
422      !!
423      !!---------------------------------------------------------------------
424      TYPE(PTRACER), DIMENSION(jptra) :: sn_tracer  ! type of tracer for saving if not key_iomput
425      !!
426      NAMELIST/namtrc/ sn_tracer, ln_trcdta,ln_trcdmp, ln_trcdmp_clo
[4154]427 
428      INTEGER  ::   ios                 ! Local integer output status for namelist read
429      INTEGER  ::   jn                  ! dummy loop indice
[4152]430      !!---------------------------------------------------------------------
431      IF(lwp) WRITE(numout,*)
432      IF(lwp) WRITE(numout,*) 'trc_nam : read the passive tracer namelists'
433      IF(lwp) WRITE(numout,*) '~~~~~~~'
434
435
436      REWIND( numnat_ref )              ! Namelist namtrc in reference namelist : Passive tracer variables
437      READ  ( numnat_ref, namtrc, IOSTAT = ios, ERR = 901)
438901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in reference namelist', lwp )
439
440      REWIND( numnat_cfg )              ! Namelist namtrc in configuration namelist : Passive tracer variables
441      READ  ( numnat_cfg, namtrc, IOSTAT = ios, ERR = 902 )
442902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc in configuration namelist', lwp )
[4624]443      IF(lwm) WRITE ( numont, namtrc )
[4152]444
445      DO jn = 1, jptra
446         ctrcnm    (jn) = TRIM( sn_tracer(jn)%clsname )
447         ctrcln    (jn) = TRIM( sn_tracer(jn)%cllname )
448         ctrcun    (jn) = TRIM( sn_tracer(jn)%clunit  )
449         ln_trc_ini(jn) =       sn_tracer(jn)%llinit
450         ln_trc_wri(jn) =       sn_tracer(jn)%llsave
451      END DO
[5726]452      IF(lwp)  CALL flush(numout)     
453
[4152]454    END SUBROUTINE trc_nam_trc
455
456
457   SUBROUTINE trc_nam_dia
458      !!---------------------------------------------------------------------
459      !!                     ***  ROUTINE trc_nam_dia  ***
460      !!
461      !! ** Purpose :   read options for the passive tracer diagnostics
462      !!
463      !! ** Method  : - read passive tracer namelist
464      !!              - read namelist of each defined SMS model
465      !!                ( (PISCES, CFC, MY_TRC )
466      !!---------------------------------------------------------------------
467      INTEGER ::  ierr
[4990]468#if defined key_trdmxl_trc  || defined key_trdtrc
[4152]469      NAMELIST/namtrc_trd/ nn_trd_trc, nn_ctls_trc, rn_ucf_trc, &
[4990]470         &                ln_trdmxl_trc_restart, ln_trdmxl_trc_instant, &
[4152]471         &                cn_trdrst_trc_in, cn_trdrst_trc_out, ln_trdtrc
472#endif
473      NAMELIST/namtrc_dia/ ln_diatrc, ln_diabio, nn_writedia, nn_writebio
474
[4154]475      INTEGER  ::   ios                 ! Local integer output status for namelist read
[4152]476      !!---------------------------------------------------------------------
477
478      IF(lwp) WRITE(numout,*) 
479      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
480      IF(lwp) WRITE(numout,*) '~~~~~~~'
481
482      IF(lwp) WRITE(numout,*)
483      IF(lwp) WRITE(numout,*) 'trc_nam_dia : read the passive tracer diagnostics options'
484      IF(lwp) WRITE(numout,*) '~~~~~~~'
485
486      REWIND( numnat_ref )              ! Namelist namtrc_dia in reference namelist : Passive tracer diagnostics
487      READ  ( numnat_ref, namtrc_dia, IOSTAT = ios, ERR = 903)
488903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in reference namelist', lwp )
489
490      REWIND( numnat_cfg )              ! Namelist namtrc_dia in configuration namelist : Passive tracer diagnostics
491      READ  ( numnat_cfg, namtrc_dia, IOSTAT = ios, ERR = 904 )
492904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namtrc_dia in configuration namelist', lwp )
[4624]493      IF(lwm) WRITE ( numont, namtrc_dia )
[4152]494
495      IF(lwp) THEN
496         WRITE(numout,*)
497         WRITE(numout,*)
498         WRITE(numout,*) ' Namelist : namtrc_dia'
499         WRITE(numout,*) '    save additionnal diagnostics arrays         ln_diatrc   = ', ln_diatrc
500         WRITE(numout,*) '    save additionnal biology diagnostics arrays ln_diabio   = ', ln_diabio
501         WRITE(numout,*) '    frequency of outputs for additional arrays  nn_writedia = ', nn_writedia
502         WRITE(numout,*) '    frequency of outputs for biological trends  nn_writebio = ', nn_writebio
503         WRITE(numout,*) ' '
[5726]504         CALL flush(numout)
[4152]505      ENDIF
[5726]506!!
507!! JPALM -- 17-07-2015 --
508!! MEDUSA is not yet up-to-date with the iom server.
509!! we use it for the main tracer, but not fully with diagnostics.
510!! will have to adapt it properly when visiting Christian Ethee
511!! for now, we change
512!! IF( ln_diatrc .AND. .NOT. lk_iomput ) THEN
513!! to :
514!!
[5939]515      IF( ( ln_diatrc .AND. .NOT. lk_iomput ) .OR. ( ln_diatrc .AND. lk_medusa ) ) THEN
[4152]516         ALLOCATE( trc2d(jpi,jpj,jpdia2d), trc3d(jpi,jpj,jpk,jpdia3d),  &
517           &       ctrc2d(jpdia2d), ctrc2l(jpdia2d), ctrc2u(jpdia2d) ,  & 
518           &       ctrc3d(jpdia3d), ctrc3l(jpdia3d), ctrc3u(jpdia3d) ,  STAT = ierr ) 
519         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate add. diag. array' )
520         !
521         trc2d(:,:,:  ) = 0._wp  ;   ctrc2d(:) = ' '   ;   ctrc2l(:) = ' '    ;    ctrc2u(:) = ' ' 
522         trc3d(:,:,:,:) = 0._wp  ;   ctrc3d(:) = ' '   ;   ctrc3l(:) = ' '    ;    ctrc3u(:) = ' ' 
523         !
[5978]524      !! ELSE IF  ( lk_iomput .AND. lk_medusa .AND. .NOT. ln_diatrc) THEN
525      !!    CALL trc_nam_iom_medusa
[4152]526      ENDIF
527
528      IF( ( ln_diabio .AND. .NOT. lk_iomput ) .OR. l_trdtrc ) THEN
529         ALLOCATE( trbio (jpi,jpj,jpk,jpdiabio) , &
530           &       ctrbio(jpdiabio), ctrbil(jpdiabio), ctrbiu(jpdiabio), STAT = ierr ) 
531         IF( ierr > 0 )   CALL ctl_stop( 'STOP', 'trcnam: unable to allocate bio. diag. array' )
532         !
533         trbio(:,:,:,:) = 0._wp  ;   ctrbio(:) = ' '   ;   ctrbil(:) = ' '    ;    ctrbiu(:) = ' ' 
534         !
535      ENDIF
536      !
537   END SUBROUTINE trc_nam_dia
538
[2038]539#else
540   !!----------------------------------------------------------------------
541   !!  Dummy module :                                     No passive tracer
542   !!----------------------------------------------------------------------
543CONTAINS
544   SUBROUTINE trc_nam                      ! Empty routine   
545   END SUBROUTINE trc_nam
[4152]546   SUBROUTINE trc_nam_run                      ! Empty routine   
547   END SUBROUTINE trc_nam_run
[2038]548#endif
549
[2104]550   !!----------------------------------------------------------------------
[2287]551   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
[5341]552   !! $Id$
[2287]553   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2038]554   !!======================================================================
555END MODULE  trcnam
Note: See TracBrowser for help on using the repository browser.