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

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

JPALM -- 23-12-2015 -- 1_ adapt CFC in MEDUSA branch - now Working properly 2_ add diagnostics to Ideal tracer

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