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 @ 5726

Last change on this file since 5726 was 5726, checked in by jpalmier, 9 years ago

JPALM -- 10-09-2015 -- add MEDUSA in the branch ; adapted TOP_SRC to MEDUSA ; remove some svn keywords in the branch

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