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_medusa.F90 in branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcnam_medusa.F90 @ 5841

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

JPALM --30-10-2015-- Add MOCSY and DMS to MEDUSA-NEMO3.6

File size: 52.5 KB
Line 
1MODULE trcnam_medusa
2   !!======================================================================
3   !!                      ***  MODULE trcnam_medusa  ***
4   !! TOP :   initialisation of some run parameters for MEDUSA bio-model
5   !!======================================================================
6   !! History :   2.0  !  2007-12  (C. Ethe, G. Madec) Original code
7   !!              -   !  2008-08  (K. Popova) adaptation for MEDUSA
8   !!              -   !  2008-11  (A. Yool) continuing adaptation for MEDUSA
9   !!              -   !  2010-03  (A. Yool) updated for branch inclusion
10   !!              -   !  2011-04  (A. Yool) updated for ROAM project
11   !!              -   !  2013-05  (A. Yool) renamed (from trclsm) for v3.5
12   !!----------------------------------------------------------------------
13#if defined key_medusa
14   !!----------------------------------------------------------------------
15   !!   'key_medusa'   :                                       MEDUSA model
16   !!----------------------------------------------------------------------
17   !! trc_nam_medusa      : MEDUSA model initialisation
18   !!----------------------------------------------------------------------
19   USE oce_trc         ! Ocean variables
20   USE par_trc         ! TOP parameters
21   USE trc             ! TOP variables
22   USE sms_medusa      ! sms trends
23   USE iom             ! I/O manager
24
25   !! AXY (04/02/14): necessary to find NaNs on HECTOR
26   USE, INTRINSIC :: ieee_arithmetic 
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   trc_nam_medusa   ! called by trcnam.F90 module
32
33   !!* Substitution
34#  include "domzgr_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
37   !! $Id$
38   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40
41CONTAINS
42
43   SUBROUTINE trc_nam_medusa
44      !!----------------------------------------------------------------------
45      !!                     ***  trc_nam_medusa  *** 
46      !!
47      !! ** Purpose :   read MEDUSA namelist
48      !!
49      !! ** input   :   file 'namelist.trc.sms' containing the following
50      !!             namelist: natbio, natopt, and natdbi ("key_trc_diabio")
51      !!
52      !! ekp: namelist nabio contains ALL parameters of the ecosystem
53      !!      point sourses and sinks PLUS sediment exchange
54      !!      dia_bio - used by Lobster to output all point terms
55      !!                (sourses and sinks of bio)
56      !!      dia_add - additional diagnostics for biology such as
57      !!                primary production (2d depth integrated field or 3d)
58      !!----------------------------------------------------------------------
59      !!
60      INTEGER            :: ji,jj,jk
61      REAL(wp)           :: fthk, fdep, fdep1
62      REAL(wp)           :: q1, q2, q3
63      !
64      NAMELIST/natbio/ xxi,xaln,xald,jphy,xvpn,xvpd,          &
65      &    xsin0,xnsi0,xuif,jliebig,                          &
66      &    xthetam,xthetamd,xnln,xnld,xsld,xfln,xfld,         &
67      &  xgmi,xgme,xkmi,xkme,xphi,xbetan,xbetac,xkc,          &
68      &    xpmipn,xpmid,xpmepn,xpmepd,xpmezmi,xpmed,          &
69      &  xmetapn,xmetapd,xmetazmi,xmetazme,                   &
70      &  jmpn,xmpn,xkphn,jmpd,xmpd,xkphd,jmzmi,xmzmi,xkzmi,   &
71      &    jmzme,xmzme,xkzme,jmd,jsfd,xmd,xmdc,               &
72      &  xthetapn,xthetapd,xthetazmi,xthetazme,xthetad,       &
73      &    xrfn,xrsn,vsed,xhr,                                &
74      &  jiron,xfe_mass,xfe_sol,xfe_sed,xLgT,xk_FeL,xk_sc_Fe, &
75      &  jexport,jfdfate,jrratio,jocalccd,xridg_r0,           &
76      &    xfdfrac1,xfdfrac2,xfdfrac3,                        &
77      &    xcaco3a,xcaco3b,xmassc,xmassca,xmasssi,xprotca,    &
78      &    xprotsi,xfastc,xfastca,xfastsi,                    &
79      &  jorgben,jinorgben,xsedn,xsedfe,xsedsi,xsedc,xsedca,  &
80      &    xburial,                                           &
81      &  jriver_n,jriver_si,jriver_c,jriver_alk,jriver_dep,   &
82      &    friver_dep,                                        &
83      &  xsdiss,                                              &
84      &  vsed,xhr,                                            &
85      &  sedlam,sedlostpoc,jpkb,jdms,jdms_input,jdms_model
86#if defined key_roam
87      NAMELIST/natroam/ xthetaphy,xthetazoo,xthetanit,        &
88      &    xthetarem,xo2min,                                  &
89      &    f3_pH,f3_h2co3,f3_hco3,f3_co3,f3_omcal,f3_omarg,   &
90      &    f2_ccd_cal,f2_ccd_arg
91#endif
92      NAMELIST/natopt/xkg0,xkr0,xkgp,xkrp,xlg,xlr,rpig
93      INTEGER :: jl, jn
94      INTEGER :: ios                 ! Local integer output status for namelist read
95      TYPE(DIAG), DIMENSION(jp_medusa_2d)  :: meddia2d
96      TYPE(DIAG), DIMENSION(jp_medusa_3d)  :: meddia3d
97      TYPE(DIAG), DIMENSION(jp_medusa_trd) :: meddiabio
98      CHARACTER(LEN=32)   ::   clname
99      !!
100      NAMELIST/nammeddia/ meddia3d, meddia2d     ! additional diagnostics
101
102      !!----------------------------------------------------------------------
103
104      IF(lwp) WRITE(numout,*)
105      clname = 'namelist_medusa'
106      IF(lwp) WRITE(numout,*) ' trc_nam_medusa: read MEDUSA namelist'
107      IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
108# if defined key_debug_medusa
109      CALL flush(numout)
110# endif
111
112
113      CALL ctl_opn( numnatp_ref, TRIM( clname )//'_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
114      CALL ctl_opn( numnatp_cfg, TRIM( clname )//'_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
115      IF(lwm) CALL ctl_opn( numonp     , 'output.namelist.pis' , 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
116
117# if defined key_debug_medusa
118      CALL flush(numout)
119      IF (lwp) write (numout,*) '------------------------------'
120      IF (lwp) write (numout,*) 'Jpalm - debug'
121      IF (lwp) write (numout,*) 'open namelist_medusa -- OK'
122      IF (lwp) write (numout,*) 'Now, read namilists inside :'
123      IF (lwp) write (numout,*) ' '
124# endif
125      !
126# if defined key_debug_medusa
127      CALL flush(numout)
128# endif
129      !
130# if defined key_debug_medusa
131      IF (lwp) write (numout,*) '------------------------------'
132      IF (lwp) write (numout,*) 'Jpalm - debug'
133      IF (lwp) write (numout,*) 'Just before reading namelist_medusa :: nammeddia'
134      IF (lwp) write (numout,*) ' '
135      CALL flush(numout)
136# endif
137
138     IF( ( .NOT.lk_iomput .AND. ln_diatrc ) .OR. ( ln_diatrc .AND. lk_medusa ) ) THEN
139         !
140         ! Namelist nammeddia
141         ! -------------------
142         REWIND( numnatp_ref )              ! Namelist nammeddia in reference namelist : MEDUSA diagnostics
143         READ  ( numnatp_ref, nammeddia, IOSTAT = ios, ERR = 901)
144901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in reference namelist', lwp )
145
146         REWIND( numnatp_cfg )              ! Namelist nammeddia in configuration namelist : MEDUSA diagnostics
147         READ  ( numnatp_cfg, nammeddia, IOSTAT = ios, ERR = 902 )
148902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in configuration namelist', lwp )
149         IF(lwm) WRITE ( numonp, nammeddia )
150
151# if defined key_debug_medusa
152         IF (lwp) write (numout,*) '------------------------------'
153         IF (lwp) write (numout,*) 'Jpalm - debug'
154         IF (lwp) write (numout,*) 'reading namelist_medusa :: nammeddia OK'
155         IF (lwp) write (numout,*) 'Check number of variable in nammeddia:'
156         IF (lwp) write (numout,*) 'jp_medusa_2d: ',jp_medusa_2d ,'jp_medusa_3d: ',jp_medusa_3d
157         IF (lwp) write (numout,*) ' '
158         CALL flush(numout)
159# endif
160         DO jl = 1, jp_medusa_2d
161            jn = jp_msa0_2d + jl - 1
162# if defined key_debug_medusa
163            IF (lwp) write (numout,*) 'Check what is readden in nammeddia: -- 2D'
164            IF (lwp) write (numout,*) jl,'meddia2d-sname: ',meddia2d(jl)%sname 
165            IF (lwp) write (numout,*) jl,'meddia2d-lname: ',meddia2d(jl)%lname 
166            IF (lwp) write (numout,*) jl,'meddia2d-units: ',meddia2d(jl)%units 
167            CALL flush(numout)
168# endif
169            ctrc2d(jn) = meddia2d(jl)%sname
170            ctrc2l(jn) = meddia2d(jl)%lname
171            ctrc2u(jn) = meddia2d(jl)%units
172         END DO
173
174         DO jl = 1, jp_medusa_3d
175            jn = jp_msa0_3d + jl - 1
176# if defined key_debug_medusa
177            IF (lwp) write (numout,*) 'Check what is readden in nammeddia: -- 3D'
178            IF (lwp) write (numout,*) jl,'meddia3d-sname: ',meddia3d(jl)%sname 
179            IF (lwp) write (numout,*) jl,'meddia3d-lname: ',meddia3d(jl)%lname
180            IF (lwp) write (numout,*) jl,'meddia3d-units: ',meddia3d(jl)%units
181            CALL flush(numout)
182# endif
183            ctrc3d(jn) = meddia3d(jl)%sname
184            ctrc3l(jn) = meddia3d(jl)%lname
185            ctrc3u(jn) = meddia3d(jl)%units
186         END DO
187
188         IF(lwp) THEN                   ! control print
189# if defined key_debug_medusa
190            IF (lwp) write (numout,*) '------------------------------'
191            IF (lwp) write (numout,*) 'Jpalm - debug'
192            IF (lwp) write (numout,*) 'Var name assignation OK'
193            IF (lwp) write (numout,*) 'next check var names'
194            IF (lwp) write (numout,*) ' '
195            CALL flush(numout)
196# endif
197            WRITE(numout,*)
198            WRITE(numout,*) ' Namelist : natadd'
199            DO jl = 1, jp_medusa_3d
200               jn = jp_msa0_3d + jl - 1
201               WRITE(numout,*) '  3d diag nb : ', jn, '    short name : ', ctrc3d(jn), &
202                 &             '  long name  : ', ctrc3l(jn), '   unit : ', ctrc3u(jn)
203            END DO
204            WRITE(numout,*) ' '
205
206            DO jl = 1, jp_medusa_2d
207               jn = jp_msa0_2d + jl - 1
208               WRITE(numout,*) '  2d diag nb : ', jn, '    short name : ', ctrc2d(jn), &
209                 &             '  long name  : ', ctrc2l(jn), '   unit : ', ctrc2u(jn)
210            END DO
211            WRITE(numout,*) ' '
212         ENDIF
213         !
214      ENDIF   
215         !
216# if defined key_debug_medusa
217            CALL flush(numout)
218# endif
219
220      ! 1.4 namelist natbio : biological parameters
221      ! -------------------------------------------
222     
223      xxi         = 0.
224      xaln        = 0.
225      xald        = 0.
226      jphy        = 0
227      xvpn        = 0.
228      xvpd        = 0.
229      xthetam     = 0.
230      xthetamd    = 0.
231!!
232      xsin0       = 0.
233      xnsi0       = 0.
234      xuif        = 0.
235!!
236      jliebig     = 0
237      xnln        = 0.
238      xnld        = 0.
239      xsld        = 0.
240      xfln        = 0.
241      xfld        = 0.
242!!
243      xgmi        = 0.
244      xgme        = 0.
245      xkmi        = 0.
246      xkme        = 0.
247      xphi    = 0.
248      xbetan      = 0.
249      xbetac      = 0.
250      xkc         = 0.
251      xpmipn      = 0.
252      xpmid       = 0.
253      xpmepn      = 0.
254      xpmepd      = 0.
255      xpmezmi     = 0.
256      xpmed       = 0.
257!!
258      xmetapn     = 0.
259      xmetapd     = 0.
260      xmetazmi    = 0.
261      xmetazme    = 0.
262!!
263      jmpn        = 0
264      xmpn        = 0.
265      xkphn       = 0.
266      jmpd        = 0
267      xmpd        = 0.
268      xkphd       = 0.
269      jmzmi       = 0
270      xmzmi       = 0.
271      xkzmi       = 0.
272      jmzme       = 0
273      xmzme       = 0.
274      xkzme       = 0.
275!!
276      jmd         = 0
277      jsfd        = 0
278      xmd         = 0.
279      xmdc        = 0.
280!!
281      xthetapn    = 0.
282      xthetapd    = 0.
283      xthetazmi   = 0.
284      xthetazme   = 0.
285      xthetad     = 0.
286      xrfn        = 0.
287      xrsn        = 0.  !: (NOT USED HERE; RETAINED FOR LOBSTER)
288!!
289      jiron       = 0
290      xfe_mass    = 0.
291      xfe_sol     = 0.
292      xfe_sed     = 0.
293      xLgT        = 0.
294      xk_FeL     = 0.
295      xk_sc_Fe    = 0.
296!!
297      jexport     = 0
298      jfdfate     = 0
299      jrratio     = 0
300      jocalccd    = 0
301      xridg_r0    = 0.
302      xfdfrac1   = 0.
303      xfdfrac2   = 0.
304      xfdfrac3   = 0.
305      xcaco3a    = 0.
306      xcaco3b    = 0.
307      xmassc     = 0.
308      xmassca    = 0.
309      xmasssi    = 0.
310      xprotca    = 0.
311      xprotsi    = 0.
312      xfastc     = 0.
313      xfastca    = 0.
314      xfastsi    = 0.
315!!
316      jorgben     = 0
317      jinorgben   = 0
318      xsedn       = 0.
319      xsedfe      = 0.
320      xsedsi      = 0.
321      xsedc       = 0.
322      xsedca      = 0.
323      xburial     = 0.
324!!
325      jriver_n    = 0
326      jriver_si   = 0
327      jriver_c    = 0
328      jriver_alk  = 0
329      jriver_dep  = 1
330!!
331      xsdiss     = 0.
332!!
333      vsed        = 0.
334      xhr         = 0.
335!!
336      sedlam     = 0.
337      sedlostpoc  = 0.
338      jpkb    = 0.
339      jdms        = 0
340      jdms_input  = 0
341      jdms_input  = 3
342           
343      !REWIND(numnatm)
344      !READ(numnatm,natbio)
345         ! Namelist natbio
346         ! -------------------
347         REWIND( numnatp_ref )              ! Namelist natbio in reference namelist : MEDUSA diagnostics
348         READ  ( numnatp_ref, natbio, IOSTAT = ios, ERR = 903)
349903      IF( ios /= 0 ) CALL ctl_nam ( ios , 'natbio in reference namelist', lwp )
350
351         REWIND( numnatp_cfg )              ! Namelist natbio in configuration namelist : MEDUSA diagnostics
352         READ  ( numnatp_cfg, natbio, IOSTAT = ios, ERR = 904 )
353904      IF( ios /= 0 ) CALL ctl_nam ( ios , 'natbio in configuration namelist', lwp )
354         IF(lwm) WRITE ( numonp, natbio )
355
356!! Primary production and chl related quantities
357!!       xxi         :  conversion factor from gC to mmolN
358!!       xaln        :  Chl-a specific initial slope of P-I curve for non-diatoms
359!!       xald        :  Chl-a specific initial slope of P-I curve for diatoms
360!!       jphy        :  phytoplankton T-dependent growth switch
361!!       xvpn        :  maximum growth rate for non-diatoms
362!!       xvpd        :  maximum growth rate for diatoms
363!!       xthetam     :  maximum Chl to C ratio for non-diatoms     
364!!       xthetamd    :  maximum Chl to C ratio for diatoms     
365!!
366!! Diatom silicon parameters
367!!       xsin0       :  minimum diatom Si:N ratio
368!!       xnsi0       :  minimum diatom N:Si ratio
369!!       xuif        :  hypothetical growth ratio at infinite Si:N ratio
370!!
371!! Nutrient limitation
372!!       jliebig     :  Liebig nutrient uptake switch
373!!       xnln        :  half-sat constant for DIN uptake by non-diatoms
374!!       xnld        :  half-sat constant for DIN uptake by diatoms
375!!       xsl         :  half-sat constant for Si uptake by diatoms
376!!       xfld        :  half-sat constant for Fe uptake by diatoms 
377!!       xfln        :  half-sat constant for Fe uptake by non-datoms
378!!
379!! Grazing
380!!       xgmi        :  microzoo maximum growth rate
381!!       xgme        :  mesozoo maximum growth rate
382!!       xkmi        :  microzoo grazing half-sat parameter
383!!       xkme        :  mesozoo grazing half-sat parameter
384!!       xphi        :  micro/mesozoo grazing inefficiency
385!!       xbetan      :  micro/mesozoo N assimilation efficiency
386!!       xbetac      :  micro/mesozoo C assimilation efficiency
387!!       xkc         :  micro/mesozoo net C growth efficiency
388!!       xpmipn      :  grazing preference of microzoo for non-diatoms
389!!       xpmid       :  grazing preference of microzoo for diatoms
390!!       xpmepn      :  grazing preference of mesozoo for non-diatoms
391!!       xpmepd      :  grazing preference of mesozoo for diatoms
392!!       xpmezmi     :  grazing preference of mesozoo for microzoo
393!!       xpmed       :  grazing preference of mesozoo for detritus
394!!
395!! Metabolic losses
396!!       xmetapn     :  non-diatom metabolic loss rate
397!!       xmetapd     :  diatom     metabolic loss rate
398!!       xmetazmi    :  microzoo   metabolic loss rate
399!!       xmetazme    :  mesozoo    metabolic loss rate
400!!
401!! Mortality/Remineralisation
402!!       jmpn        :  non-diatom mortality functional form
403!!       xmpn        :  non-diatom mortality rate
404!!       xkphn       :  non-diatom mortality half-sat constant
405!!       jmpd        :  diatom     mortality functional form
406!!       xmpd        :  diatom mortality rate
407!!       xkphd       :  diatom mortality half-sat constant
408!!       jmzmi       :  microzoo   mortality functional form
409!!       xmzmi       :  microzoo mortality rate
410!!       xkzmi       :  microzoo mortality half-sat constant
411!!       jmzme       :  mesozoo    mortality functional form
412!!       xmzme       :  mesozoo mortality rate
413!!       xkzme       :  mesozoo mortality half-sat constant
414!!
415!! Remineralisation
416!!       jmd         :  detritus T-dependent remineralisation switch
417!!       jsfd        :  accelerate seafloor detritus remin. switch
418!!       xmd         :  detrital nitrogen remineralisation rate
419!!       xmdc        :  detrital carbon remineralisation rate
420!!
421!! Stochiometric ratios
422!!       xthetapn    :  non-diatom C:N ratio
423!!       xthetapd    :  diatom C:N ratio
424!!       xthetazmi   :  microzoo C:N ratio
425!!       xthetazme   :  mesozoo C:N ratio
426!!       xthetad     :  detritus C:N ratio
427!!       xrfn        :  phytoplankton Fe:N ratio
428!!  xrsn        :  diatom Si:N ratio (*NOT* used)
429!!
430!! Iron parameters
431!!       jiron       :  iron scavenging submodel switch
432!!       xfe_mass    :  iron atomic mass
433!!  xfe_sol     :  aeolian iron solubility
434!!  xfe_sed     :  sediment iron input
435!!  xLgT      :  total ligand concentration (umol/m3)
436!!  xk_FeL       :  dissociation constant for (Fe + L)
437!!  xk_sc_Fe    :  scavenging rate of "free" iron
438!! 
439!! Fast-sinking detritus parameters
440!!       jexport     :  fast detritus remineralisation switch
441!!       jfdfate     :  fate of fast detritus at seafloor switch
442!!       jrratio     :  rain ratio switch
443!!       jocalccd    :  CCD switch
444!!       xridg_r0    :  Ridgwell rain ratio coefficient
445!!       xfdfrac1    :  fast-sinking fraction of diatom nat. mort. losses
446!!       xfdfrac2    :  fast-sinking fraction of meszooplankton mort. losses
447!!       xfdfrac3    :  fast-sinking fraction of diatom silicon grazing losses
448!!       xcaco3a     :  polar (high latitude) CaCO3 fraction
449!!       xcaco3b     :  equatorial (low latitude) CaCO3 fraction
450!!       xmassc      :  organic C mass:mole ratio, C106 H175 O40 N16 P1
451!!       xmassca     :  calcium carbonate mass:mole ratio, CaCO3
452!!       xmasssi     :  biogenic silicon mass:mole ratio, (H2SiO3)n
453!!       xprotca     :  calcium carbonate protection ratio
454!!       xprotsi     :  biogenic silicon protection ratio
455!!       xfastc      :  organic C remineralisation length scale
456!!       xfastca     :  calcium carbonate dissolution length scale
457!!       xfastsi     :  biogenic silicon dissolution length scale
458!!
459!! Benthic
460!!       jorgben     :  does   organic detritus go to the benthos?
461!!       jinorgben   :  does inorganic detritus go to the benthos?
462!!       xsedn       :  organic   nitrogen sediment remineralisation rate
463!!       xsedfe      :  organic   iron     sediment remineralisation rate
464!!       xsedsi      :  inorganic silicon  sediment dissolution      rate
465!!       xsedc       :  organic   carbon   sediment remineralisation rate
466!!       xsedca      :  inorganic carbon   sediment dissolution      rate
467!!       xburial     :  burial rate of seafloor detritus
468!!
469!! Riverine inputs
470!!       jriver_n    :  riverine N          input?
471!!       jriver_si   :  riverine Si         input?
472!!       jriver_c    :  riverine C          input?
473!!       jriver_alk  :  riverine alkalinity input?
474!!       jriver_dep  :  depth of riverine   input?
475!!
476!! Miscellaneous
477!!       xsdiss      :  diatom frustule dissolution rate
478!!
479!! Gravitational sinking     
480!!       vsed        :  detritus gravitational sinking rate
481!!       xhr         :  coeff for Martin's remineralisation profile
482!!
483!! Additional parameters
484!!       sedlam      :  time coeff of POC in sediments
485!!      sedlostpoc   :  sediment geol loss for POC
486!!       jpkb        :  vertical layer for diagnostic of the vertical flux
487!!                      NOTE that in LOBSTER it is a first vertical layers where
488!!                      biology is active 
489!!
490!! UKESM1 - new diagnostics  !! Jpalm
491!!       jdms        :  include dms diagnostics
492!!  jdms_input  :  use instant (0) or diel-avg (1) inputs
493!!       jdms_model  :  choice of DMS model passed to atmosphere
494!!                      1 = ANDR, 2 = SIMO, 3 = ARAN, 4 = HALL
495!!
496      IF(lwp) THEN
497!!
498!! AXY (08/11/13): compilation key notification
499         WRITE(numout,*) '=== Compilation keys'
500#if defined key_roam
501         WRITE(numout,*)     &
502         &   ' key_roam                                                               = ACTIVE'
503#else
504         WRITE(numout,*)     &
505         &   ' key_roam                                                               = INACTIVE'
506#endif       
507#if defined key_axy_carbchem
508         WRITE(numout,*)     &
509         &   ' key_axy_carbchem                                                       = ACTIVE'
510#else
511         WRITE(numout,*)     &
512         &   ' key_axy_carbchem                                                       = INACTIVE'
513#endif       
514#if defined key_mocsy
515         WRITE(numout,*)     &
516         &   ' key_mocsy                                                              = ACTIVE'
517#else
518         WRITE(numout,*)     &
519         &   ' key_mocsy                                                              = INACTIVE'
520#endif       
521#if defined key_avgqsr_medusa
522         WRITE(numout,*)     &
523         &   ' key_avgqsr_medusa                                                      = ACTIVE'
524#else
525         WRITE(numout,*)     &
526         &   ' key_avgqsr_medusa                                                      = INACTIVE'
527#endif       
528#if defined key_bs_axy_zforce
529         WRITE(numout,*)     &
530         &   ' key_bs_axy_zforce                                                      = ACTIVE'
531#else
532         WRITE(numout,*)     &
533         &   ' key_bs_axy_zforce                                                      = INACTIVE'
534#endif       
535#if defined key_bs_axy_yrlen
536         WRITE(numout,*)     &
537         &   ' key_bs_axy_yrlen                                                       = ACTIVE'
538#else
539         WRITE(numout,*)     &
540         &   ' key_bs_axy_yrlen                                                       = INACTIVE'
541#endif       
542#if defined key_deep_fe_fix
543         WRITE(numout,*)     &
544         &   ' key_deep_fe_fix                                                        = ACTIVE'
545#else
546         WRITE(numout,*)     &
547         &   ' key_deep_fe_fix                                                        = INACTIVE'
548#endif       
549#if defined key_axy_nancheck
550         WRITE(numout,*)     &
551         &   ' key_axy_nancheck                                                       = ACTIVE'
552#else
553         WRITE(numout,*)     &
554         &   ' key_axy_nancheck                                                       = INACTIVE'
555#endif       
556# if defined key_axy_pi_co2
557         WRITE(numout,*)     &
558         &   ' key_axy_pi_co2                                                         = ACTIVE'
559#else
560         WRITE(numout,*)     &
561         &   ' key_axy_pi_co2                                                         = INACTIVE'
562# endif
563# if defined key_debug_medusa
564         WRITE(numout,*)     &
565         &   ' key_debug_medusa                                                       = ACTIVE'
566#else
567         WRITE(numout,*)     &
568         &   ' key_debug_medusa                                                       = INACTIVE'
569# endif
570         WRITE(numout,*) ' '
571
572         WRITE(numout,*) 'natbio'
573         WRITE(numout,*) ' '
574!!
575!! Primary production and chl related quantities
576         WRITE(numout,*) '=== Primary production'
577         WRITE(numout,*)     &
578         &   ' conversion factor from gC to mmolN,                        xxi         =', xxi
579         WRITE(numout,*)     &
580         &   ' Chl-a specific initial slope of P-I curve for non-diatoms, xaln        = ', xaln
581         WRITE(numout,*)     &
582         &   ' Chl-a specific initial slope of P-I curve for diatoms,     xald        = ', xald
583         if (jphy.eq.1) then
584            WRITE(numout,*) &
585            &   ' phytoplankton growth is *temperature-dependent*            jphy        = ', jphy
586         elseif (jphy.eq.0) then
587            WRITE(numout,*) &
588            &   ' phytoplankton growth is *temperature-independent*          jphy        = ', jphy
589         endif
590         WRITE(numout,*)     &
591         &   ' maximum growth rate for non-diatoms,                       xvpn        = ', xvpn
592         WRITE(numout,*)     &
593         &   ' maximum growth rate for diatoms,                           xvpn        = ', xvpd
594         WRITE(numout,*)     &
595         &   ' maximum Chl to C ratio for non-diatoms,                    xthetam     = ', xthetam
596         WRITE(numout,*)     &
597         &   ' maximum Chl to C ratio for diatoms,                        xthetamd    = ', xthetamd
598!!
599!! Diatom silicon parameters
600         WRITE(numout,*) '=== Diatom silicon parameters'
601         WRITE(numout,*)     &
602         &   ' minimum diatom Si:N ratio,                                 xsin0       = ', xsin0
603         WRITE(numout,*)     &
604         &   ' minimum diatom N:Si ratio,                                 xnsi0       = ', xnsi0
605         WRITE(numout,*)     &
606         &   ' hypothetical growth ratio at infinite Si:N ratio,          xuif        = ', xuif
607!!
608!! Nutrient limitation
609         WRITE(numout,*) '=== Nutrient limitation'
610         if (jliebig.eq.1) then
611            WRITE(numout,*) &
612            &   ' nutrient uptake is a Liebig Law (= most limiting) function jliebig     = ', jliebig
613         elseif (jliebig.eq.0) then
614            WRITE(numout,*) &
615            &   ' nutrient uptake is a multiplicative function               jliebig     = ', jliebig
616         endif
617         WRITE(numout,*)     &
618         &   ' half-sat constant for DIN uptake by non-diatoms,           xnln        = ', xnln
619         WRITE(numout,*)     &
620         &   ' half-sat constant for DIN uptake by diatoms,               xnld        = ', xnld
621         WRITE(numout,*)     &
622         &   ' half-sat constant for Si uptake by diatoms,                xsld        = ', xsld
623         WRITE(numout,*)     &
624         &   ' half-sat constant for Fe uptake by non-diatoms,            xfln        = ', xfln
625         WRITE(numout,*)     &
626         &   ' half-sat constant for Fe uptake by diatoms,                xfld        = ', xfld
627!!
628!! Grazing
629         WRITE(numout,*) '=== Zooplankton grazing'
630         WRITE(numout,*)     &
631         &   ' microzoo maximum growth rate,                              xgmi        = ', xgmi
632         WRITE(numout,*)     &
633         &   ' mesozoo maximum growth rate,                               xgme        = ', xgme
634         WRITE(numout,*)     &
635         &   ' microzoo grazing half-sat parameter,                       xkmi        = ', xkmi
636         WRITE(numout,*)     &
637         &   ' mesozoo grazing half-sat parameter,                        xkme        = ', xkme
638         WRITE(numout,*)     &
639         &   ' micro/mesozoo grazing inefficiency,                        xphi        = ', xphi
640         WRITE(numout,*)     &
641         &   ' micro/mesozoo N assimilation efficiency,                   xbetan      = ', xbetan
642         WRITE(numout,*)     &
643         &   ' micro/mesozoo C assimilation efficiency,                   xbetac      = ', xbetan
644         WRITE(numout,*)     &
645         &   ' micro/mesozoo net C growth efficiency,                     xkc         = ', xkc
646         WRITE(numout,*)     &
647         &   ' grazing preference of microzoo for non-diatoms,            xpmipn      = ', xpmipn
648         WRITE(numout,*)     &
649         &   ' grazing preference of microzoo for detritus,               xpmid       = ', xpmid
650         WRITE(numout,*)     &
651         &   ' grazing preference of mesozoo for non-diatoms,             xpmepn      = ', xpmepn
652         WRITE(numout,*)     &
653         &   ' grazing preference of mesozoo for diatoms,                 xpmepd      = ', xpmepd
654         WRITE(numout,*)     &
655         &   ' grazing preference of mesozoo for microzoo,                xpmezmi     = ', xpmezmi
656         WRITE(numout,*)     &
657         &   ' grazing preference of mesozoo for detritus,                xpmed       = ', xpmed
658!!
659!! Metabolic losses
660         WRITE(numout,*) '=== Metabolic losses'
661         WRITE(numout,*)     &
662         &   ' non-diatom metabolic loss rate,                            xmetapn     = ', xmetapn
663         WRITE(numout,*)     &
664         &   ' diatom     metabolic loss rate,                            xmetapd     = ', xmetapd
665         WRITE(numout,*)     &
666         &   ' microzoo   metabolic loss rate,                            xmetazmi    = ', xmetazmi
667         WRITE(numout,*)     &
668         &   ' mesozoo    metabolic loss rate,                            xmetazme    = ', xmetazme
669!!
670!! Mortality losses
671         WRITE(numout,*) '=== Mortality losses'
672         if (jmpn.eq.1) then
673            WRITE(numout,*)     &
674            &   ' non-diatom mortality functional form,            LINEAR    jmpn        = ', jmpn
675         elseif (jmpn.eq.2) then
676            WRITE(numout,*)     &
677            &   ' non-diatom mortality functional form,         QUADRATIC    jmpn        = ', jmpn
678         elseif (jmpn.eq.3) then
679            WRITE(numout,*)     &
680            &   ' non-diatom mortality functional form,        HYPERBOLIC    jmpn        = ', jmpn
681         elseif (jmpn.eq.4) then
682            WRITE(numout,*)     &
683            &   ' non-diatom mortality functional form,           SIGMOID    jmpn        = ', jmpn
684         endif
685         WRITE(numout,*)     &
686         &   ' non-diatom mortality rate,                                 xmpn        = ', xmpn
687         WRITE(numout,*)     &
688         &   ' non-diatom mortality half-sat constant                     xkphn       = ', xkphn
689         if (jmpd.eq.1) then
690            WRITE(numout,*)     &
691            &   ' diatom mortality functional form,                LINEAR    jmpd        = ', jmpd
692         elseif (jmpd.eq.2) then
693            WRITE(numout,*)     &
694            &   ' diatom mortality functional form,             QUADRATIC    jmpd        = ', jmpd
695         elseif (jmpd.eq.3) then
696            WRITE(numout,*)     &
697            &   ' diatom mortality functional form,            HYPERBOLIC    jmpd        = ', jmpd
698         elseif (jmpd.eq.4) then
699            WRITE(numout,*)     &
700            &   ' diatom mortality functional form,               SIGMOID    jmpd        = ', jmpd
701         endif
702         WRITE(numout,*)     &
703         &   ' diatom mortality rate,                                     xmpd        = ', xmpd
704         WRITE(numout,*)     &
705         &   ' diatom mortality half-sat constant                         xkphd       = ', xkphd
706         if (jmzmi.eq.1) then
707            WRITE(numout,*)     &
708            &   ' microzoo mortality functional form,              LINEAR    jmzmi       = ', jmzmi
709         elseif (jmzmi.eq.2) then
710            WRITE(numout,*)     &
711            &   ' microzoo mortality functional form,           QUADRATIC    jmzmi       = ', jmzmi
712         elseif (jmzmi.eq.3) then
713            WRITE(numout,*)     &
714            &   ' microzoo mortality functional form,          HYPERBOLIC    jmzmi       = ', jmzmi
715         elseif (jmzmi.eq.4) then
716            WRITE(numout,*)     &
717            &   ' microzoo mortality functional form,             SIGMOID    jmzmi       = ', jmzmi
718         endif
719         WRITE(numout,*)     &
720         &   ' microzoo mortality rate,                                   xmzmi       = ', xmzmi
721         WRITE(numout,*)     &
722         &   ' mesozoo mortality half-sat constant,                       xkzmi       = ', xkzmi
723         if (jmzme.eq.1) then
724            WRITE(numout,*)     &
725            &   ' mesozoo mortality functional form,               LINEAR    jmzme       = ', jmzme
726         elseif (jmzme.eq.2) then
727            WRITE(numout,*)     &
728            &   ' mesozoo mortality functional form,            QUADRATIC    jmzme       = ', jmzme
729         elseif (jmzme.eq.3) then
730            WRITE(numout,*)     &
731            &   ' mesozoo mortality functional form,           HYPERBOLIC    jmzme       = ', jmzme
732         elseif (jmzme.eq.4) then
733            WRITE(numout,*)     &
734            &   ' mesozoo mortality functional form,              SIGMOID    jmzme       = ', jmzme
735         endif
736         WRITE(numout,*)     &
737         &   ' mesozoo mortality rate,                                    xmzme       = ', xmzme
738         WRITE(numout,*)     &
739         &   ' mesozoo mortality half-sat constant,                       xkzme       = ', xkzme
740!!
741!! Remineralisation
742         WRITE(numout,*) '=== Remineralisation'
743         if (jmd.eq.1) then
744            WRITE(numout,*) &
745            &   ' detritus remineralisation is *temperature-dependent*       jmd         = ', jmd
746         elseif (jmd.eq.0) then
747            WRITE(numout,*) &
748            &   ' detritus remineralisation is *temperature-independent*     jmd         = ', jmd
749         endif
750         if (jsfd.eq.1) then
751            WRITE(numout,*) &
752            &   ' detritus seafloor remineralisation is *accelerated*        jsfd        = ', jsfd
753         else
754            WRITE(numout,*) &
755            &   ' detritus seafloor remineralisation occurs at same rate     jsfd        = ', jsfd
756         endif
757         WRITE(numout,*)     &
758         &   ' detrital nitrogen remineralisation rate,                   xmd         = ', xmd
759         WRITE(numout,*)     &
760         &   ' detrital carbon remineralisation rate,                     xmdc        = ', xmdc
761!!
762!! Stochiometric ratios
763         WRITE(numout,*) '=== Stoichiometric ratios'
764         WRITE(numout,*)     &
765         &   ' non-diatom C:N ratio,                                      xthetapn    = ', xthetapn
766         WRITE(numout,*)     &
767         &   ' diatom C:N ratio,                                          xthetapd    = ', xthetapd
768         WRITE(numout,*)     &
769         &   ' microzoo C:N ratio,                                        xthetazmi   = ', xthetazmi
770         WRITE(numout,*)     &
771         &   ' mesozoo C:N ratio,                                         xthetazme   = ', xthetazme
772         WRITE(numout,*)     &
773         &   ' detritus C:N ratio,                                        xthetad     = ', xthetad
774         WRITE(numout,*)     &
775         &   ' phytoplankton Fe:N ratio,                                  xrfn        = ', xrfn
776         WRITE(numout,*)     &
777         &   ' diatom Si:N ratio,                                         xrsn        = ', xrsn
778!!   
779!! Iron parameters
780         WRITE(numout,*) '=== Iron parameters'
781         if (jiron.eq.1) then
782            WRITE(numout,*)     &
783            &   ' Dutkiewicz et al. (2005) iron scavenging                   jiron       = ', jiron
784         elseif (jiron.eq.2) then
785            WRITE(numout,*)     &
786            &   ' Moore et al. (2004) iron scavenging                        jiron       = ', jiron
787         elseif (jiron.eq.3) then
788            WRITE(numout,*)     &
789            &   ' Moore et al. (2008) iron scavenging                        jiron       = ', jiron
790         elseif (jiron.eq.4) then
791            WRITE(numout,*)     &
792            &   ' Galbraith et al. (2010) iron scavenging                    jiron       = ', jiron
793         else
794            WRITE(numout,*)     &
795            &   ' There is **no** iron scavenging                            jiron       = ', jiron
796         endif
797         WRITE(numout,*)     &
798         &   ' iron atomic mass,                                          xfe_mass    = ', xfe_mass
799         WRITE(numout,*)     &
800         &   ' aeolian iron solubility,                                   xfe_sol     = ', xfe_sol
801         WRITE(numout,*)     &
802         &   ' sediment iron input,                                       xfe_sed     = ', xfe_sed
803         WRITE(numout,*)     &
804         &   ' total ligand concentration (umol/m3),                      xLgT        = ', xLgT
805         WRITE(numout,*)     &
806         &   ' dissociation constant for (Fe + L),                        xk_FeL      = ', xk_FeL
807         WRITE(numout,*)     &
808         &   ' scavenging rate for free iron,                             xk_sc_Fe    = ', xk_sc_Fe
809!!
810!! Fast-sinking detritus parameters
811         WRITE(numout,*) '=== Fast-sinking detritus'
812         if (jexport.eq.1) then
813            WRITE(numout,*) &
814            &   ' fast-detritus remin. uses Dunne et al. (2007; ballast)     jexport     = ', jexport
815         elseif (jexport.eq.2) then
816            WRITE(numout,*) &
817            &   ' fast-detritus remin. uses Martin et al. (1987)             jexport     = ', jexport
818         elseif (jexport.eq.2) then
819            WRITE(numout,*) &
820            &   ' fast-detritus remin. uses Henson et al. (2011)             jexport     = ', jexport
821         endif
822         if (jfdfate.eq.1) then
823            WRITE(numout,*) &
824            &   ' fast-detritus reaching seafloor becomes slow-detritus      jfdfate     = ', jfdfate
825         elseif (jfdfate.eq.0) then
826            WRITE(numout,*) &
827            &   ' fast-detritus reaching seafloor instantly remineralised    jfdfate     = ', jfdfate
828         endif
829#if defined key_roam
830         if (jrratio.eq.0) then
831            WRITE(numout,*) &
832            &   ' Dunne et al. (2005) rain ratio submodel                    jrratio     = ', jrratio
833         elseif (jrratio.eq.1) then
834            WRITE(numout,*) &
835            &   ' Ridgwell et al. (2007) rain ratio submodel (surface omega) jrratio     = ', jrratio
836         elseif (jrratio.eq.2) then
837            WRITE(numout,*) &
838            &   ' Ridgwell et al. (2007) rain ratio submodel (3D omega)      jrratio     = ', jrratio
839         endif
840#else         
841         jrratio = 0
842         WRITE(numout,*) &
843         &   ' Dunne et al. (2005) rain ratio submodel                    jrratio     = ', jrratio
844#endif         
845#if defined key_roam
846         if (jocalccd.eq.0) then
847            WRITE(numout,*) &
848            &   ' Default, fixed CCD used                                    jocalccd    = ', jocalccd
849         elseif (jocalccd.eq.1) then
850            WRITE(numout,*) &
851            &   ' Calculated, dynamic CCD used                               jocalccd    = ', jocalccd
852         endif
853#else         
854         jocalccd = 0
855         WRITE(numout,*) &
856         &   ' Default, fixed CCD used                                    jocalccd    = ', jocalccd
857#endif
858         WRITE(numout,*)     &
859         &   ' Ridgwell rain ratio coefficient,                           xridg_r0    = ', xridg_r0
860         WRITE(numout,*)     &
861         &   ' fast-sinking fraction of diatom nat. mort. losses,         xfdfrac1    = ', xfdfrac1
862         WRITE(numout,*)     &
863         &   ' fast-sinking fraction of mesozooplankton mort. losses,     xfdfrac2    = ', xfdfrac2
864         WRITE(numout,*)     &
865         &   ' fast-sinking fraction of diatom silicon grazing losses,    xfdfrac3    = ', xfdfrac3
866         WRITE(numout,*)     &
867         &   ' polar (high latitude) CaCO3 fraction,                      xcaco3a     = ', xcaco3a
868         WRITE(numout,*)     &
869         &   ' equatorial (low latitude) CaCO3 fraction,                  xcaco3b     = ', xcaco3b
870         WRITE(numout,*)     &
871         &   ' organic C mass:mole ratio, C106 H175 O40 N16 P1,           xmassc      = ', xmassc
872         WRITE(numout,*)     &
873         &   ' calcium carbonate mass:mole ratio, CaCO3,                  xmassca     = ', xmassca
874         WRITE(numout,*)     &
875         &   ' biogenic silicon mass:mole ratio, (H2SiO3)n,               xmasssi     = ', xmasssi
876         WRITE(numout,*)     &
877         &   ' calcium carbonate protection ratio,                        xprotca     = ', xprotca
878         WRITE(numout,*)     &
879         &   ' biogenic silicon protection ratio,                         xprotsi     = ', xprotsi
880         WRITE(numout,*)     &
881         &   ' organic C remineralisation length scale,                   xfastc      = ', xfastc
882         WRITE(numout,*)     &
883         &   ' calcium carbonate dissolution length scale,                xfastca     = ', xfastca
884         WRITE(numout,*)     &
885         &   ' biogenic silicon dissolution length scale,                 xfastsi     = ', xfastsi
886!!
887!! Benthos parameters
888         WRITE(numout,*) '=== Benthos parameters'
889         WRITE(numout,*)     &
890         &   ' does   organic detritus go to the benthos?,                jorgben     = ', jorgben
891         WRITE(numout,*)     &
892         &   ' does inorganic detritus go to the benthos?,                jinorgben   = ', jinorgben
893!!
894!! Some checks on parameters related to benthos parameters
895         if (jorgben.eq.1 .and. jsfd.eq.1) then
896            !! slow detritus going to benthos at an accelerated rate
897            WRITE(numout,*) '  === WARNING! ==='
898            WRITE(numout,*) '  jsfd *and* jorgben are active - please check that you wish this'
899            WRITE(numout,*) '  === WARNING! ==='
900         endif
901         if (jorgben.eq.1 .and. jfdfate.eq.1) then
902            !! fast detritus going to benthos but via slow detritus
903            WRITE(numout,*) '  === WARNING! ==='
904            WRITE(numout,*) '  jfdfate *and* jorgben are active - please check that you wish this'
905            WRITE(numout,*) '  === WARNING! ==='
906         endif
907         if (jorgben.eq.0 .and. jinorgben.eq.1) then
908            !! inorganic fast detritus going to benthos but organic fast detritus is not
909            WRITE(numout,*) '  === WARNING! ==='
910            WRITE(numout,*) '  jinorgben is active but jorgben is not - please check that you wish this'
911            WRITE(numout,*) '  === WARNING! ==='
912         endif
913         WRITE(numout,*)     &
914         &   ' organic   nitrogen sediment remineralisation rate,         xsedn       = ', xsedn
915         WRITE(numout,*)     &
916         &   ' organic   iron     sediment remineralisation rate,         xsedfe      = ', xsedfe
917         WRITE(numout,*)     &
918         &   ' inorganic silicon  sediment remineralisation rate,         xsedsi      = ', xsedsi
919         WRITE(numout,*)     &
920         &   ' organic   carbon   sediment remineralisation rate,         xsedc       = ', xsedc
921         WRITE(numout,*)     &
922         &   ' inorganic carbon   sediment remineralisation rate,         xsedca      = ', xsedca
923         WRITE(numout,*)     &
924         &   ' burial rate of seafloor detritus,                          xburial     = ', xburial
925!!
926!! Riverine inputs
927         WRITE(numout,*) '=== Riverine inputs'
928         if (jriver_n.eq.0) then
929            WRITE(numout,*)     &
930            &   ' *no* riverine N input,                                     jriver_n    = ', jriver_n
931         elseif (jriver_n.eq.1) then
932            WRITE(numout,*)     &
933            &   ' riverine N concentrations specified,                       jriver_n    = ', jriver_n
934         elseif (jriver_n.eq.2) then
935            WRITE(numout,*)     &
936            &   ' riverine N inputs specified,                               jriver_n    = ', jriver_n
937         endif
938         if (jriver_si.eq.0) then
939            WRITE(numout,*)     &
940            &   ' *no* riverine Si input,                                    jriver_si   = ', jriver_si
941         elseif (jriver_si.eq.1) then
942            WRITE(numout,*)     &
943            &   ' riverine Si concentrations specified,                      jriver_si   = ', jriver_si
944         elseif (jriver_si.eq.2) then
945            WRITE(numout,*)     &
946            &   ' riverine Si inputs specified,                              jriver_si   = ', jriver_si
947         endif
948         if (jriver_c.eq.0) then
949            WRITE(numout,*)     &
950            &   ' *no* riverine C input,                                     jriver_c    = ', jriver_c
951         elseif (jriver_c.eq.1) then
952            WRITE(numout,*)     &
953            &   ' riverine C concentrations specified,                       jriver_c    = ', jriver_c
954         elseif (jriver_c.eq.2) then
955            WRITE(numout,*)     &
956            &   ' riverine C inputs specified,                               jriver_c    = ', jriver_c
957         endif
958         if (jriver_alk.eq.0) then
959            WRITE(numout,*)     &
960            &   ' *no* riverine alkalinity input,                            jriver_alk  = ', jriver_alk
961         elseif (jriver_alk.eq.1) then
962            WRITE(numout,*)     &
963            &   ' riverine alkalinity concentrations specified,              jriver_alk  = ', jriver_alk
964         elseif (jriver_alk.eq.2) then
965            WRITE(numout,*)     &
966            &   ' riverine alkalinity inputs specified,                      jriver_alk  = ', jriver_alk
967         endif
968         !! AXY (19/07/12): prevent (gross) stupidity on part of user
969         if (jriver_dep.lt.1.or.jriver_dep.ge.jpk) then
970            jriver_dep = 1
971         endif
972         WRITE(numout,*)     &
973         &   ' riverine input applied to down to depth k = ...            jriver_dep  = ', jriver_dep
974!!
975!! Miscellaneous
976         WRITE(numout,*) '=== Miscellaneous'
977         WRITE(numout,*)     &
978         &   ' diatom frustule dissolution rate,                          xsdiss      = ', xsdiss
979!!
980!! Gravitational sinking     
981         WRITE(numout,*) '=== Gravitational sinking'
982         WRITE(numout,*)     &
983         &   ' detritus gravitational sinking rate,                       vsed        = ', vsed
984         WRITE(numout,*)     & 
985         &   ' coefficient for Martin et al. (1987) remineralisation,     xhr         = ', xhr
986!!
987!! Non-Medusa parameters
988         WRITE(numout,*) '=== Non-Medusa parameters'
989         WRITE(numout,*)     & 
990         &   ' time coeff of POC in sediments,                            sedlam      = ', sedlam
991         WRITE(numout,*)     &
992         &   ' Sediment geol loss for POC,                                sedlostpoc  = ', sedlostpoc
993         WRITE(numout,*)     &
994         &   ' Vert layer for diagnostic of vertical flux,                jpkp        = ', jpkb
995!!
996!! UKESM1 - new diagnostics  !! Jpalm; AXY (08/07/15)
997         WRITE(numout,*) '=== UKESM1-related parameters'
998         WRITE(numout,*)     &
999         &   ' include DMS diagnostic?,                                   jdms        = ', jdms
1000         if (jdms_input .eq. 0) then
1001            WRITE(numout,*)     &
1002            &   ' use instant (0) or diel-avg (1) inputs,                    jdms_input  = instantaneous'
1003         else
1004            WRITE(numout,*)     &
1005            &   ' use instant (0) or diel-avg (1) inputs,                    jdms_input  = diel-average'
1006         endif
1007    if (jdms_model .eq. 1) then
1008            WRITE(numout,*)     &
1009            &   ' choice of DMS model passed to atmosphere,                  jdms_model  = Anderson et al. (2001)'
1010    elseif (jdms_model .eq. 2) then
1011            WRITE(numout,*)     &
1012            &   ' choice of DMS model passed to atmosphere,                  jdms_model  = Simo & Dachs (2002)'
1013    elseif (jdms_model .eq. 3) then
1014            WRITE(numout,*)     &
1015            &   ' choice of DMS model passed to atmosphere,                  jdms_model  = Aranami & Tsunogai (2004)'
1016    elseif (jdms_model .eq. 4) then
1017            WRITE(numout,*)     &
1018            &   ' choice of DMS model passed to atmosphere,                  jdms_model  = Halloran et al. (2010)'
1019         endif
1020!!
1021      ENDIF
1022!!
1023!! Key depth positions (with thanks to Andrew Coward for bug-fixing this bit)
1024      DO jk = 1,jpk
1025         !! level thickness
1026         fthk  = e3t_1d(jk)
1027         !! level depth (top of level)
1028         fdep  = gdepw_1d(jk)
1029         !! level depth (bottom of level)
1030         fdep1 = fdep + fthk
1031         !!
1032         if (fdep.lt.100.0.AND.fdep1.gt.100.0) then        !  100 m
1033            i0100 = jk
1034         elseif (fdep.lt.150.0.AND.fdep1.gt.150.0) then    !  150 m (for BASIN)
1035            i0150 = jk
1036         elseif (fdep.lt.200.0.AND.fdep1.gt.200.0) then    !  200 m
1037            i0200 = jk
1038         elseif (fdep.lt.500.0.AND.fdep1.gt.500.0) then    !  500 m
1039            i0500 = jk
1040         elseif (fdep.lt.1000.0.AND.fdep1.gt.1000.0) then  ! 1000 m
1041            i1000 = jk
1042         elseif (fdep1.lt.1100.0) then                     ! 1100 m (for Moore et al. sedimentary iron)
1043            i1100 = jk
1044         endif
1045      enddo
1046      !!
1047      IF(lwp) THEN
1048          WRITE(numout,*) '=== Position of key depths'
1049          WRITE(numout,*)     & 
1050          &   ' jk position of  100 m horizon                              i0100       = ', i0100
1051          WRITE(numout,*)     &
1052          &   ' jk position of  150 m horizon                              i0150       = ', i0150
1053          WRITE(numout,*)     & 
1054          &   ' jk position of  200 m horizon                              i0200       = ', i0200
1055          WRITE(numout,*)     & 
1056          &   ' jk position of  500 m horizon                              i0500       = ', i0500
1057          WRITE(numout,*)     & 
1058          &   ' jk position of 1000 m horizon                              i1000       = ', i1000
1059          WRITE(numout,*)     & 
1060          &   ' jk position of 1100 m horizon [*]                          i1100       = ', i1100
1061          WRITE(numout,*) 'Got here ' , SIZE(friver_dep)
1062          CALL flush(numout)
1063      ENDIF
1064
1065#if defined key_roam
1066
1067      ! 1.4b namelist natroam : ROAM parameters
1068      ! ---------------------------------------
1069     
1070      xthetaphy = 0.
1071      xthetazoo = 0.
1072      xthetanit = 0.
1073      xthetarem = 0.
1074      xo2min    = 0.
1075
1076      !READ(numnatm,natroam)
1077         ! Namelist natroam
1078         ! -------------------
1079         REWIND( numnatp_ref )              ! Namelist natroam in reference namelist : MEDUSA diagnostics
1080         READ  ( numnatp_ref, natroam, IOSTAT = ios, ERR = 905)
1081905      IF( ios /= 0 ) CALL ctl_nam ( ios , 'natroam in reference namelist', lwp )
1082
1083         REWIND( numnatp_cfg )              ! Namelist natroam in configuration namelist : MEDUSA diagnostics
1084         READ  ( numnatp_cfg, natroam, IOSTAT = ios, ERR = 906 )
1085906      IF( ios /= 0 ) CALL ctl_nam ( ios , 'natroam in configuration namelist', lwp )
1086         IF(lwm) WRITE ( numonp, natroam )
1087
1088!! ROAM carbon, alkalinity and oxygen cycle parameters
1089!!       xthetaphy :  oxygen evolution/consumption by phytoplankton
1090!!       xthetazoo :  oxygen consumption by zooplankton
1091!!       xthetanit :  oxygen consumption by nitrogen remineralisation
1092!!       xthetarem :  oxygen consumption by carbon remineralisation
1093!!       xo2min    :  oxygen minimum concentration
1094
1095      IF(lwp) THEN
1096          WRITE(numout,*) 'natroam'
1097          WRITE(numout,*) ' '
1098!!
1099!! ROAM carbon, alkalinity and oxygen cycle parameters
1100          WRITE(numout,*) '=== ROAM carbon, alkalinity and oxygen cycle parameters'
1101          WRITE(numout,*)     &
1102          &   ' oxygen evolution/consumption by phytoplankton              xthetaphy   = ', xthetaphy
1103          WRITE(numout,*)     &
1104          &   ' oxygen consumption by zooplankton                          xthetazoo   = ', xthetazoo
1105          WRITE(numout,*)     &
1106          &   ' oxygen consumption by nitrogen remineralisation            xthetanit   = ', xthetanit
1107          WRITE(numout,*)     &
1108          &   ' oxygen consumption by carbon remineralisation              xthetarem   = ', xthetarem
1109          WRITE(numout,*)     &
1110          &   ' oxygen minimum concentration                               xo2min      = ', xo2min
1111       ENDIF
1112
1113#endif
1114
1115      CALL flush(numout)
1116
1117      ! 1.5 namelist natopt : parameters for optic
1118      ! ------------------------------------------
1119
1120      xkg0  = 0.
1121      xkr0  = 0.
1122      xkgp  = 0.
1123      xkrp  = 0.
1124      xlg   = 0.
1125      xlr   = 0.
1126      rpig  = 0.
1127
1128      !READ(numnatm,natopt)
1129         ! Namelist natopt
1130         ! -------------------
1131         REWIND( numnatp_ref )              ! Namelist natopt in reference namelist : MEDUSA diagnostics
1132         READ  ( numnatp_ref, natopt, IOSTAT = ios, ERR = 907)
1133907      IF( ios /= 0 ) CALL ctl_nam ( ios , 'natopt in reference namelist', lwp )
1134
1135         REWIND( numnatp_cfg )              ! Namelist natopt in configuration namelist : MEDUSA diagnostics
1136         READ  ( numnatp_cfg, natopt, IOSTAT = ios, ERR = 908 )
1137908      IF( ios /= 0 ) CALL ctl_nam ( ios , 'natopt in configuration namelist', lwp )
1138         IF(lwm) WRITE ( numonp, natopt )
1139
1140      IF(lwp) THEN
1141         WRITE(numout,*) 'natopt'
1142         WRITE(numout,*) ' '
1143         WRITE(numout,*) ' green   water absorption coeff  xkg0  = ',xkg0
1144         WRITE(numout,*) ' red water absorption coeff      xkr0  = ',xkr0
1145         WRITE(numout,*) ' pigment red absorption coeff    xkrp  = ',xkrp
1146         WRITE(numout,*) ' pigment green absorption coeff  xkgp  = ',xkgp
1147         WRITE(numout,*) ' green chl exposant              xlg   = ',xlg
1148         WRITE(numout,*) ' red   chl exposant              xlr   = ',xlr
1149         WRITE(numout,*) ' chla/chla+phea ratio            rpig  = ',rpig
1150         WRITE(numout,*) ' '
1151
1152      ENDIF
1153
1154      IF(lwp) THEN
1155         WRITE(numout,*) 'NaN check'
1156         WRITE(numout,*) ' '
1157         q1 = -1.
1158         q2 = 0.
1159         q3 = log(q1)
1160         write (numout,*) 'q3 = ', q3
1161         if ( ieee_is_nan( q3 ) ) then
1162            write (numout,*) 'NaN detected'
1163         else
1164            write (numout,*) 'NaN not detected'
1165         endif
1166         WRITE(numout,*) ' '
1167       ENDIF
1168
1169   END SUBROUTINE trc_nam_medusa
1170   
1171#else
1172   !!----------------------------------------------------------------------
1173   !!  Dummy module :                                             No MEDUSA
1174   !!----------------------------------------------------------------------
1175CONTAINS
1176   SUBROUTINE trc_nam_medusa                      ! Empty routine
1177   END  SUBROUTINE  trc_nam_medusa
1178#endif 
1179
1180   !!======================================================================
1181END MODULE trcnam_medusa
Note: See TracBrowser for help on using the repository browser.