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_r5107_NOC_MEDUSA/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5107_NOC_MEDUSA/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcnam_medusa.F90 @ 5710

Last change on this file since 5710 was 5710, checked in by acc, 9 years ago

Branch NERC/dev_r5107_NOC_MEDUSA. Removed SVN keyword updating and cleared existing expansions.

File size: 50.4 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
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 nampisdia
141         ! -------------------
142         REWIND( numnatp_ref )              ! Namelist nampisdia in reference namelist : Pisces 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 nampisdia in configuration namelist : Pisces 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           
341      !REWIND(numnatm)
342      !READ(numnatm,natbio)
343         ! Namelist natbio
344         ! -------------------
345         REWIND( numnatp_ref )              ! Namelist nampisdia in reference namelist : Pisces diagnostics
346         READ  ( numnatp_ref, natbio, IOSTAT = ios, ERR = 901)
347901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in reference namelist', lwp )
348
349         REWIND( numnatp_cfg )              ! Namelist nampisdia in configuration namelist : Pisces diagnostics
350         READ  ( numnatp_cfg, natbio, IOSTAT = ios, ERR = 902 )
351902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in configuration namelist', lwp )
352         IF(lwm) WRITE ( numonp, natbio )
353
354!! Primary production and chl related quantities
355!!       xxi         :  conversion factor from gC to mmolN
356!!       xaln        :  Chl-a specific initial slope of P-I curve for non-diatoms
357!!       xald        :  Chl-a specific initial slope of P-I curve for diatoms
358!!       jphy        :  phytoplankton T-dependent growth switch
359!!       xvpn        :  maximum growth rate for non-diatoms
360!!       xvpd        :  maximum growth rate for diatoms
361!!       xthetam     :  maximum Chl to C ratio for non-diatoms     
362!!       xthetamd    :  maximum Chl to C ratio for diatoms     
363!!
364!! Diatom silicon parameters
365!!       xsin0       :  minimum diatom Si:N ratio
366!!       xnsi0       :  minimum diatom N:Si ratio
367!!       xuif        :  hypothetical growth ratio at infinite Si:N ratio
368!!
369!! Nutrient limitation
370!!       jliebig     :  Liebig nutrient uptake switch
371!!       xnln        :  half-sat constant for DIN uptake by non-diatoms
372!!       xnld        :  half-sat constant for DIN uptake by diatoms
373!!       xsl         :  half-sat constant for Si uptake by diatoms
374!!       xfld        :  half-sat constant for Fe uptake by diatoms 
375!!       xfln        :  half-sat constant for Fe uptake by non-datoms
376!!
377!! Grazing
378!!       xgmi        :  microzoo maximum growth rate
379!!       xgme        :  mesozoo maximum growth rate
380!!       xkmi        :  microzoo grazing half-sat parameter
381!!       xkme        :  mesozoo grazing half-sat parameter
382!!       xphi        :  micro/mesozoo grazing inefficiency
383!!       xbetan      :  micro/mesozoo N assimilation efficiency
384!!       xbetac      :  micro/mesozoo C assimilation efficiency
385!!       xkc         :  micro/mesozoo net C growth efficiency
386!!       xpmipn      :  grazing preference of microzoo for non-diatoms
387!!       xpmid       :  grazing preference of microzoo for diatoms
388!!       xpmepn      :  grazing preference of mesozoo for non-diatoms
389!!       xpmepd      :  grazing preference of mesozoo for diatoms
390!!       xpmezmi     :  grazing preference of mesozoo for microzoo
391!!       xpmed       :  grazing preference of mesozoo for detritus
392!!
393!! Metabolic losses
394!!       xmetapn     :  non-diatom metabolic loss rate
395!!       xmetapd     :  diatom     metabolic loss rate
396!!       xmetazmi    :  microzoo   metabolic loss rate
397!!       xmetazme    :  mesozoo    metabolic loss rate
398!!
399!! Mortality/Remineralisation
400!!       jmpn        :  non-diatom mortality functional form
401!!       xmpn        :  non-diatom mortality rate
402!!       xkphn       :  non-diatom mortality half-sat constant
403!!       jmpd        :  diatom     mortality functional form
404!!       xmpd        :  diatom mortality rate
405!!       xkphd       :  diatom mortality half-sat constant
406!!       jmzmi       :  microzoo   mortality functional form
407!!       xmzmi       :  microzoo mortality rate
408!!       xkzmi       :  microzoo mortality half-sat constant
409!!       jmzme       :  mesozoo    mortality functional form
410!!       xmzme       :  mesozoo mortality rate
411!!       xkzme       :  mesozoo mortality half-sat constant
412!!
413!! Remineralisation
414!!       jmd         :  detritus T-dependent remineralisation switch
415!!       jsfd        :  accelerate seafloor detritus remin. switch
416!!       xmd         :  detrital nitrogen remineralisation rate
417!!       xmdc        :  detrital carbon remineralisation rate
418!!
419!! Stochiometric ratios
420!!       xthetapn    :  non-diatom C:N ratio
421!!       xthetapd    :  diatom C:N ratio
422!!       xthetazmi   :  microzoo C:N ratio
423!!       xthetazme   :  mesozoo C:N ratio
424!!       xthetad     :  detritus C:N ratio
425!!       xrfn        :  phytoplankton Fe:N ratio
426!!  xrsn        :  diatom Si:N ratio (*NOT* used)
427!!
428!! Iron parameters
429!!       jiron       :  iron scavenging submodel switch
430!!       xfe_mass    :  iron atomic mass
431!!  xfe_sol     :  aeolian iron solubility
432!!  xfe_sed     :  sediment iron input
433!!  xLgT      :  total ligand concentration (umol/m3)
434!!  xk_FeL       :  dissociation constant for (Fe + L)
435!!  xk_sc_Fe    :  scavenging rate of "free" iron
436!! 
437!! Fast-sinking detritus parameters
438!!       jexport     :  fast detritus remineralisation switch
439!!       jfdfate     :  fate of fast detritus at seafloor switch
440!!       jrratio     :  rain ratio switch
441!!       jocalccd    :  CCD switch
442!!       xridg_r0    :  Ridgwell rain ratio coefficient
443!!       xfdfrac1    :  fast-sinking fraction of diatom nat. mort. losses
444!!       xfdfrac2    :  fast-sinking fraction of meszooplankton mort. losses
445!!       xfdfrac3    :  fast-sinking fraction of diatom silicon grazing losses
446!!       xcaco3a     :  polar (high latitude) CaCO3 fraction
447!!       xcaco3b     :  equatorial (low latitude) CaCO3 fraction
448!!       xmassc      :  organic C mass:mole ratio, C106 H175 O40 N16 P1
449!!       xmassca     :  calcium carbonate mass:mole ratio, CaCO3
450!!       xmasssi     :  biogenic silicon mass:mole ratio, (H2SiO3)n
451!!       xprotca     :  calcium carbonate protection ratio
452!!       xprotsi     :  biogenic silicon protection ratio
453!!       xfastc      :  organic C remineralisation length scale
454!!       xfastca     :  calcium carbonate dissolution length scale
455!!       xfastsi     :  biogenic silicon dissolution length scale
456!!
457!! Benthic
458!!       jorgben     :  does   organic detritus go to the benthos?
459!!       jinorgben   :  does inorganic detritus go to the benthos?
460!!       xsedn       :  organic   nitrogen sediment remineralisation rate
461!!       xsedfe      :  organic   iron     sediment remineralisation rate
462!!       xsedsi      :  inorganic silicon  sediment dissolution      rate
463!!       xsedc       :  organic   carbon   sediment remineralisation rate
464!!       xsedca      :  inorganic carbon   sediment dissolution      rate
465!!       xburial     :  burial rate of seafloor detritus
466!!
467!! Riverine inputs
468!!       jriver_n    :  riverine N          input?
469!!       jriver_si   :  riverine Si         input?
470!!       jriver_c    :  riverine C          input?
471!!       jriver_alk  :  riverine alkalinity input?
472!!       jriver_dep  :  depth of riverine   input?
473!!
474!! Miscellaneous
475!!       xsdiss      :  diatom frustule dissolution rate
476!!
477!! Gravitational sinking     
478!!       vsed        :  detritus gravitational sinking rate
479!!       xhr         :  coeff for Martin's remineralisation profile
480!!
481!! Additional parameters
482!!       sedlam      :  time coeff of POC in sediments
483!!      sedlostpoc   :  sediment geol loss for POC
484!!       jpkb        :  vertical layer for diagnostic of the vertical flux
485!!                      NOTE that in LOBSTER it is a first vertical layers where
486!!                      biology is active 
487!!
488!! UKESM1 - new diagnostics  !! Jpalm
489!!       jdms        :  include dms diagnostics
490!!
491!!
492!!
493
494      IF(lwp) THEN
495!!
496!! AXY (08/11/13): compilation key notification
497         WRITE(numout,*) '=== Compilation keys'
498#if defined key_roam
499         WRITE(numout,*)     &
500         &   ' key_roam                                                               = ACTIVE'
501#else
502         WRITE(numout,*)     &
503         &   ' key_roam                                                               = INACTIVE'
504#endif       
505#if defined key_axy_carbchem
506         WRITE(numout,*)     &
507         &   ' key_axy_carbchem                                                       = ACTIVE'
508#else
509         WRITE(numout,*)     &
510         &   ' key_axy_carbchem                                                       = INACTIVE'
511#endif       
512#if defined key_bs_axy_zforce
513         WRITE(numout,*)     &
514         &   ' key_bs_axy_zforce                                                      = ACTIVE'
515#else
516         WRITE(numout,*)     &
517         &   ' key_bs_axy_zforce                                                      = INACTIVE'
518#endif       
519#if defined key_bs_axy_yrlen
520         WRITE(numout,*)     &
521         &   ' key_bs_axy_yrlen                                                       = ACTIVE'
522#else
523         WRITE(numout,*)     &
524         &   ' key_bs_axy_yrlen                                                       = INACTIVE'
525#endif       
526#if defined key_deep_fe_fix
527         WRITE(numout,*)     &
528         &   ' key_deep_fe_fix                                                        = ACTIVE'
529#else
530         WRITE(numout,*)     &
531         &   ' key_deep_fe_fix                                                        = INACTIVE'
532#endif       
533#if defined key_axy_nancheck
534         WRITE(numout,*)     &
535         &   ' key_axy_nancheck                                                       = ACTIVE'
536#else
537         WRITE(numout,*)     &
538         &   ' key_axy_nancheck                                                       = INACTIVE'
539#endif       
540# if defined key_axy_pi_co2
541         WRITE(numout,*)     &
542         &   ' key_axy_pi_co2                                                         = ACTIVE'
543#else
544         WRITE(numout,*)     &
545         &   ' key_axy_pi_co2                                                         = INACTIVE'
546# endif
547         WRITE(numout,*) ' '
548
549         WRITE(numout,*) 'natbio'
550         WRITE(numout,*) ' '
551!!
552!! Primary production and chl related quantities
553         WRITE(numout,*) '=== Primary production'
554         WRITE(numout,*)     &
555         &   ' conversion factor from gC to mmolN,                        xxi         =', xxi
556         WRITE(numout,*)     &
557         &   ' Chl-a specific initial slope of P-I curve for non-diatoms, xaln        = ', xaln
558         WRITE(numout,*)     &
559         &   ' Chl-a specific initial slope of P-I curve for diatoms,     xald        = ', xald
560         if (jphy.eq.1) then
561            WRITE(numout,*) &
562            &   ' phytoplankton growth is *temperature-dependent*            jphy        = ', jphy
563         elseif (jphy.eq.0) then
564            WRITE(numout,*) &
565            &   ' phytoplankton growth is *temperature-independent*          jphy        = ', jphy
566         endif
567         WRITE(numout,*)     &
568         &   ' maximum growth rate for non-diatoms,                       xvpn        = ', xvpn
569         WRITE(numout,*)     &
570         &   ' maximum growth rate for diatoms,                           xvpn        = ', xvpd
571         WRITE(numout,*)     &
572         &   ' maximum Chl to C ratio for non-diatoms,                    xthetam     = ', xthetam
573         WRITE(numout,*)     &
574         &   ' maximum Chl to C ratio for diatoms,                        xthetamd    = ', xthetamd
575!!
576!! Diatom silicon parameters
577         WRITE(numout,*) '=== Diatom silicon parameters'
578         WRITE(numout,*)     &
579         &   ' minimum diatom Si:N ratio,                                 xsin0       = ', xsin0
580         WRITE(numout,*)     &
581         &   ' minimum diatom N:Si ratio,                                 xnsi0       = ', xnsi0
582         WRITE(numout,*)     &
583         &   ' hypothetical growth ratio at infinite Si:N ratio,          xuif        = ', xuif
584!!
585!! Nutrient limitation
586         WRITE(numout,*) '=== Nutrient limitation'
587         if (jliebig.eq.1) then
588            WRITE(numout,*) &
589            &   ' nutrient uptake is a Liebig Law (= most limiting) function jliebig     = ', jliebig
590         elseif (jliebig.eq.0) then
591            WRITE(numout,*) &
592            &   ' nutrient uptake is a multiplicative function               jliebig     = ', jliebig
593         endif
594         WRITE(numout,*)     &
595         &   ' half-sat constant for DIN uptake by non-diatoms,           xnln        = ', xnln
596         WRITE(numout,*)     &
597         &   ' half-sat constant for DIN uptake by diatoms,               xnld        = ', xnld
598         WRITE(numout,*)     &
599         &   ' half-sat constant for Si uptake by diatoms,                xsld        = ', xsld
600         WRITE(numout,*)     &
601         &   ' half-sat constant for Fe uptake by non-diatoms,            xfln        = ', xfln
602         WRITE(numout,*)     &
603         &   ' half-sat constant for Fe uptake by diatoms,                xfld        = ', xfld
604!!
605!! Grazing
606         WRITE(numout,*) '=== Zooplankton grazing'
607         WRITE(numout,*)     &
608         &   ' microzoo maximum growth rate,                              xgmi        = ', xgmi
609         WRITE(numout,*)     &
610         &   ' mesozoo maximum growth rate,                               xgme        = ', xgme
611         WRITE(numout,*)     &
612         &   ' microzoo grazing half-sat parameter,                       xkmi        = ', xkmi
613         WRITE(numout,*)     &
614         &   ' mesozoo grazing half-sat parameter,                        xkme        = ', xkme
615         WRITE(numout,*)     &
616         &   ' micro/mesozoo grazing inefficiency,                        xphi        = ', xphi
617         WRITE(numout,*)     &
618         &   ' micro/mesozoo N assimilation efficiency,                   xbetan      = ', xbetan
619         WRITE(numout,*)     &
620         &   ' micro/mesozoo C assimilation efficiency,                   xbetac      = ', xbetan
621         WRITE(numout,*)     &
622         &   ' micro/mesozoo net C growth efficiency,                     xkc         = ', xkc
623         WRITE(numout,*)     &
624         &   ' grazing preference of microzoo for non-diatoms,            xpmipn      = ', xpmipn
625         WRITE(numout,*)     &
626         &   ' grazing preference of microzoo for detritus,               xpmid       = ', xpmid
627         WRITE(numout,*)     &
628         &   ' grazing preference of mesozoo for non-diatoms,             xpmepn      = ', xpmepn
629         WRITE(numout,*)     &
630         &   ' grazing preference of mesozoo for diatoms,                 xpmepd      = ', xpmepd
631         WRITE(numout,*)     &
632         &   ' grazing preference of mesozoo for microzoo,                xpmezmi     = ', xpmezmi
633         WRITE(numout,*)     &
634         &   ' grazing preference of mesozoo for detritus,                xpmed       = ', xpmed
635!!
636!! Metabolic losses
637         WRITE(numout,*) '=== Metabolic losses'
638         WRITE(numout,*)     &
639         &   ' non-diatom metabolic loss rate,                            xmetapn     = ', xmetapn
640         WRITE(numout,*)     &
641         &   ' diatom     metabolic loss rate,                            xmetapd     = ', xmetapd
642         WRITE(numout,*)     &
643         &   ' microzoo   metabolic loss rate,                            xmetazmi    = ', xmetazmi
644         WRITE(numout,*)     &
645         &   ' mesozoo    metabolic loss rate,                            xmetazme    = ', xmetazme
646!!
647!! Mortality losses
648         WRITE(numout,*) '=== Mortality losses'
649         if (jmpn.eq.1) then
650            WRITE(numout,*)     &
651            &   ' non-diatom mortality functional form,            LINEAR    jmpn        = ', jmpn
652         elseif (jmpn.eq.2) then
653            WRITE(numout,*)     &
654            &   ' non-diatom mortality functional form,         QUADRATIC    jmpn        = ', jmpn
655         elseif (jmpn.eq.3) then
656            WRITE(numout,*)     &
657            &   ' non-diatom mortality functional form,        HYPERBOLIC    jmpn        = ', jmpn
658         elseif (jmpn.eq.4) then
659            WRITE(numout,*)     &
660            &   ' non-diatom mortality functional form,           SIGMOID    jmpn        = ', jmpn
661         endif
662         WRITE(numout,*)     &
663         &   ' non-diatom mortality rate,                                 xmpn        = ', xmpn
664         WRITE(numout,*)     &
665         &   ' non-diatom mortality half-sat constant                     xkphn       = ', xkphn
666         if (jmpd.eq.1) then
667            WRITE(numout,*)     &
668            &   ' diatom mortality functional form,                LINEAR    jmpd        = ', jmpd
669         elseif (jmpd.eq.2) then
670            WRITE(numout,*)     &
671            &   ' diatom mortality functional form,             QUADRATIC    jmpd        = ', jmpd
672         elseif (jmpd.eq.3) then
673            WRITE(numout,*)     &
674            &   ' diatom mortality functional form,            HYPERBOLIC    jmpd        = ', jmpd
675         elseif (jmpd.eq.4) then
676            WRITE(numout,*)     &
677            &   ' diatom mortality functional form,               SIGMOID    jmpd        = ', jmpd
678         endif
679         WRITE(numout,*)     &
680         &   ' diatom mortality rate,                                     xmpd        = ', xmpd
681         WRITE(numout,*)     &
682         &   ' diatom mortality half-sat constant                         xkphd       = ', xkphd
683         if (jmzmi.eq.1) then
684            WRITE(numout,*)     &
685            &   ' microzoo mortality functional form,              LINEAR    jmzmi       = ', jmzmi
686         elseif (jmzmi.eq.2) then
687            WRITE(numout,*)     &
688            &   ' microzoo mortality functional form,           QUADRATIC    jmzmi       = ', jmzmi
689         elseif (jmzmi.eq.3) then
690            WRITE(numout,*)     &
691            &   ' microzoo mortality functional form,          HYPERBOLIC    jmzmi       = ', jmzmi
692         elseif (jmzmi.eq.4) then
693            WRITE(numout,*)     &
694            &   ' microzoo mortality functional form,             SIGMOID    jmzmi       = ', jmzmi
695         endif
696         WRITE(numout,*)     &
697         &   ' microzoo mortality rate,                                   xmzmi       = ', xmzmi
698         WRITE(numout,*)     &
699         &   ' mesozoo mortality half-sat constant,                       xkzmi       = ', xkzmi
700         if (jmzme.eq.1) then
701            WRITE(numout,*)     &
702            &   ' mesozoo mortality functional form,               LINEAR    jmzme       = ', jmzme
703         elseif (jmzme.eq.2) then
704            WRITE(numout,*)     &
705            &   ' mesozoo mortality functional form,            QUADRATIC    jmzme       = ', jmzme
706         elseif (jmzme.eq.3) then
707            WRITE(numout,*)     &
708            &   ' mesozoo mortality functional form,           HYPERBOLIC    jmzme       = ', jmzme
709         elseif (jmzme.eq.4) then
710            WRITE(numout,*)     &
711            &   ' mesozoo mortality functional form,              SIGMOID    jmzme       = ', jmzme
712         endif
713         WRITE(numout,*)     &
714         &   ' mesozoo mortality rate,                                    xmzme       = ', xmzme
715         WRITE(numout,*)     &
716         &   ' mesozoo mortality half-sat constant,                       xkzme       = ', xkzme
717!!
718!! Remineralisation
719         WRITE(numout,*) '=== Remineralisation'
720         if (jmd.eq.1) then
721            WRITE(numout,*) &
722            &   ' detritus remineralisation is *temperature-dependent*       jmd         = ', jmd
723         elseif (jmd.eq.0) then
724            WRITE(numout,*) &
725            &   ' detritus remineralisation is *temperature-independent*     jmd         = ', jmd
726         endif
727         if (jsfd.eq.1) then
728            WRITE(numout,*) &
729            &   ' detritus seafloor remineralisation is *accelerated*        jsfd        = ', jsfd
730         else
731            WRITE(numout,*) &
732            &   ' detritus seafloor remineralisation occurs at same rate     jsfd        = ', jsfd
733         endif
734         WRITE(numout,*)     &
735         &   ' detrital nitrogen remineralisation rate,                   xmd         = ', xmd
736         WRITE(numout,*)     &
737         &   ' detrital carbon remineralisation rate,                     xmdc        = ', xmdc
738!!
739!! Stochiometric ratios
740         WRITE(numout,*) '=== Stoichiometric ratios'
741         WRITE(numout,*)     &
742         &   ' non-diatom C:N ratio,                                      xthetapn    = ', xthetapn
743         WRITE(numout,*)     &
744         &   ' diatom C:N ratio,                                          xthetapd    = ', xthetapd
745         WRITE(numout,*)     &
746         &   ' microzoo C:N ratio,                                        xthetazmi   = ', xthetazmi
747         WRITE(numout,*)     &
748         &   ' mesozoo C:N ratio,                                         xthetazme   = ', xthetazme
749         WRITE(numout,*)     &
750         &   ' detritus C:N ratio,                                        xthetad     = ', xthetad
751         WRITE(numout,*)     &
752         &   ' phytoplankton Fe:N ratio,                                  xrfn        = ', xrfn
753         WRITE(numout,*)     &
754         &   ' diatom Si:N ratio,                                         xrsn        = ', xrsn
755!!   
756!! Iron parameters
757         WRITE(numout,*) '=== Iron parameters'
758         if (jiron.eq.1) then
759            WRITE(numout,*)     &
760            &   ' Dutkiewicz et al. (2005) iron scavenging                   jiron       = ', jiron
761         elseif (jiron.eq.2) then
762            WRITE(numout,*)     &
763            &   ' Moore et al. (2004) iron scavenging                        jiron       = ', jiron
764         elseif (jiron.eq.3) then
765            WRITE(numout,*)     &
766            &   ' Moore et al. (2008) iron scavenging                        jiron       = ', jiron
767         elseif (jiron.eq.4) then
768            WRITE(numout,*)     &
769            &   ' Galbraith et al. (2010) iron scavenging                    jiron       = ', jiron
770         else
771            WRITE(numout,*)     &
772            &   ' There is **no** iron scavenging                            jiron       = ', jiron
773         endif
774         WRITE(numout,*)     &
775         &   ' iron atomic mass,                                          xfe_mass    = ', xfe_mass
776         WRITE(numout,*)     &
777         &   ' aeolian iron solubility,                                   xfe_sol     = ', xfe_sol
778         WRITE(numout,*)     &
779         &   ' sediment iron input,                                       xfe_sed     = ', xfe_sed
780         WRITE(numout,*)     &
781         &   ' total ligand concentration (umol/m3),                      xLgT        = ', xLgT
782         WRITE(numout,*)     &
783         &   ' dissociation constant for (Fe + L),                        xk_FeL      = ', xk_FeL
784         WRITE(numout,*)     &
785         &   ' scavenging rate for free iron,                             xk_sc_Fe    = ', xk_sc_Fe
786!!
787!! Fast-sinking detritus parameters
788         WRITE(numout,*) '=== Fast-sinking detritus'
789         if (jexport.eq.1) then
790            WRITE(numout,*) &
791            &   ' fast-detritus remin. uses Dunne et al. (2007; ballast)     jexport     = ', jexport
792         elseif (jexport.eq.2) then
793            WRITE(numout,*) &
794            &   ' fast-detritus remin. uses Martin et al. (1987)             jexport     = ', jexport
795         elseif (jexport.eq.2) then
796            WRITE(numout,*) &
797            &   ' fast-detritus remin. uses Henson et al. (2011)             jexport     = ', jexport
798         endif
799         if (jfdfate.eq.1) then
800            WRITE(numout,*) &
801            &   ' fast-detritus reaching seafloor becomes slow-detritus      jfdfate     = ', jfdfate
802         elseif (jfdfate.eq.0) then
803            WRITE(numout,*) &
804            &   ' fast-detritus reaching seafloor instantly remineralised    jfdfate     = ', jfdfate
805         endif
806#if defined key_roam
807         if (jrratio.eq.0) then
808            WRITE(numout,*) &
809            &   ' Dunne et al. (2005) rain ratio submodel                    jrratio     = ', jrratio
810         elseif (jrratio.eq.1) then
811            WRITE(numout,*) &
812            &   ' Ridgwell et al. (2007) rain ratio submodel (surface omega) jrratio     = ', jrratio
813         elseif (jrratio.eq.2) then
814            WRITE(numout,*) &
815            &   ' Ridgwell et al. (2007) rain ratio submodel (3D omega)      jrratio     = ', jrratio
816         endif
817#else         
818         jrratio = 0
819         WRITE(numout,*) &
820         &   ' Dunne et al. (2005) rain ratio submodel                    jrratio     = ', jrratio
821#endif         
822#if defined key_roam
823         if (jocalccd.eq.0) then
824            WRITE(numout,*) &
825            &   ' Default, fixed CCD used                                    jocalccd    = ', jocalccd
826         elseif (jocalccd.eq.1) then
827            WRITE(numout,*) &
828            &   ' Calculated, dynamic CCD used                               jocalccd    = ', jocalccd
829         endif
830#else         
831         jocalccd = 0
832         WRITE(numout,*) &
833         &   ' Default, fixed CCD used                                    jocalccd    = ', jocalccd
834#endif
835         WRITE(numout,*)     &
836         &   ' Ridgwell rain ratio coefficient,                           xridg_r0    = ', xridg_r0
837         WRITE(numout,*)     &
838         &   ' fast-sinking fraction of diatom nat. mort. losses,         xfdfrac1    = ', xfdfrac1
839         WRITE(numout,*)     &
840         &   ' fast-sinking fraction of mesozooplankton mort. losses,     xfdfrac2    = ', xfdfrac2
841         WRITE(numout,*)     &
842         &   ' fast-sinking fraction of diatom silicon grazing losses,    xfdfrac3    = ', xfdfrac3
843         WRITE(numout,*)     &
844         &   ' polar (high latitude) CaCO3 fraction,                      xcaco3a     = ', xcaco3a
845         WRITE(numout,*)     &
846         &   ' equatorial (low latitude) CaCO3 fraction,                  xcaco3b     = ', xcaco3b
847         WRITE(numout,*)     &
848         &   ' organic C mass:mole ratio, C106 H175 O40 N16 P1,           xmassc      = ', xmassc
849         WRITE(numout,*)     &
850         &   ' calcium carbonate mass:mole ratio, CaCO3,                  xmassca     = ', xmassca
851         WRITE(numout,*)     &
852         &   ' biogenic silicon mass:mole ratio, (H2SiO3)n,               xmasssi     = ', xmasssi
853         WRITE(numout,*)     &
854         &   ' calcium carbonate protection ratio,                        xprotca     = ', xprotca
855         WRITE(numout,*)     &
856         &   ' biogenic silicon protection ratio,                         xprotsi     = ', xprotsi
857         WRITE(numout,*)     &
858         &   ' organic C remineralisation length scale,                   xfastc      = ', xfastc
859         WRITE(numout,*)     &
860         &   ' calcium carbonate dissolution length scale,                xfastca     = ', xfastca
861         WRITE(numout,*)     &
862         &   ' biogenic silicon dissolution length scale,                 xfastsi     = ', xfastsi
863!!
864!! Benthos parameters
865         WRITE(numout,*) '=== Benthos parameters'
866         WRITE(numout,*)     &
867         &   ' does   organic detritus go to the benthos?,                jorgben     = ', jorgben
868         WRITE(numout,*)     &
869         &   ' does inorganic detritus go to the benthos?,                jinorgben   = ', jinorgben
870!!
871!! Some checks on parameters related to benthos parameters
872         if (jorgben.eq.1 .and. jsfd.eq.1) then
873            !! slow detritus going to benthos at an accelerated rate
874            WRITE(numout,*) '  === WARNING! ==='
875            WRITE(numout,*) '  jsfd *and* jorgben are active - please check that you wish this'
876            WRITE(numout,*) '  === WARNING! ==='
877         endif
878         if (jorgben.eq.1 .and. jfdfate.eq.1) then
879            !! fast detritus going to benthos but via slow detritus
880            WRITE(numout,*) '  === WARNING! ==='
881            WRITE(numout,*) '  jfdfate *and* jorgben are active - please check that you wish this'
882            WRITE(numout,*) '  === WARNING! ==='
883         endif
884         if (jorgben.eq.0 .and. jinorgben.eq.1) then
885            !! inorganic fast detritus going to benthos but organic fast detritus is not
886            WRITE(numout,*) '  === WARNING! ==='
887            WRITE(numout,*) '  jinorgben is active but jorgben is not - please check that you wish this'
888            WRITE(numout,*) '  === WARNING! ==='
889         endif
890         WRITE(numout,*)     &
891         &   ' organic   nitrogen sediment remineralisation rate,         xsedn       = ', xsedn
892         WRITE(numout,*)     &
893         &   ' organic   iron     sediment remineralisation rate,         xsedfe      = ', xsedfe
894         WRITE(numout,*)     &
895         &   ' inorganic silicon  sediment remineralisation rate,         xsedsi      = ', xsedsi
896         WRITE(numout,*)     &
897         &   ' organic   carbon   sediment remineralisation rate,         xsedc       = ', xsedc
898         WRITE(numout,*)     &
899         &   ' inorganic carbon   sediment remineralisation rate,         xsedca      = ', xsedca
900         WRITE(numout,*)     &
901         &   ' burial rate of seafloor detritus,                          xburial     = ', xburial
902!!
903!! Riverine inputs
904         WRITE(numout,*) '=== Riverine inputs'
905         if (jriver_n.eq.0) then
906            WRITE(numout,*)     &
907            &   ' *no* riverine N input,                                     jriver_n    = ', jriver_n
908         elseif (jriver_n.eq.1) then
909            WRITE(numout,*)     &
910            &   ' riverine N concentrations specified,                       jriver_n    = ', jriver_n
911         elseif (jriver_n.eq.2) then
912            WRITE(numout,*)     &
913            &   ' riverine N inputs specified,                               jriver_n    = ', jriver_n
914         endif
915         if (jriver_si.eq.0) then
916            WRITE(numout,*)     &
917            &   ' *no* riverine Si input,                                    jriver_si   = ', jriver_si
918         elseif (jriver_si.eq.1) then
919            WRITE(numout,*)     &
920            &   ' riverine Si concentrations specified,                      jriver_si   = ', jriver_si
921         elseif (jriver_si.eq.2) then
922            WRITE(numout,*)     &
923            &   ' riverine Si inputs specified,                              jriver_si   = ', jriver_si
924         endif
925         if (jriver_c.eq.0) then
926            WRITE(numout,*)     &
927            &   ' *no* riverine C input,                                     jriver_c    = ', jriver_c
928         elseif (jriver_c.eq.1) then
929            WRITE(numout,*)     &
930            &   ' riverine C concentrations specified,                       jriver_c    = ', jriver_c
931         elseif (jriver_c.eq.2) then
932            WRITE(numout,*)     &
933            &   ' riverine C inputs specified,                               jriver_c    = ', jriver_c
934         endif
935         if (jriver_alk.eq.0) then
936            WRITE(numout,*)     &
937            &   ' *no* riverine alkalinity input,                            jriver_alk  = ', jriver_alk
938         elseif (jriver_alk.eq.1) then
939            WRITE(numout,*)     &
940            &   ' riverine alkalinity concentrations specified,              jriver_alk  = ', jriver_alk
941         elseif (jriver_alk.eq.2) then
942            WRITE(numout,*)     &
943            &   ' riverine alkalinity inputs specified,                      jriver_alk  = ', jriver_alk
944         endif
945         !! AXY (19/07/12): prevent (gross) stupidity on part of user
946         if (jriver_dep.lt.1.or.jriver_dep.ge.jpk) then
947            jriver_dep = 1
948         endif
949         WRITE(numout,*)     &
950         &   ' riverine input applied to down to depth k = ...            jriver_dep  = ', jriver_dep
951!!
952!! Miscellaneous
953         WRITE(numout,*) '=== Miscellaneous'
954         WRITE(numout,*)     &
955         &   ' diatom frustule dissolution rate,                          xsdiss      = ', xsdiss
956!!
957!! Gravitational sinking     
958         WRITE(numout,*) '=== Gravitational sinking'
959         WRITE(numout,*)     &
960         &   ' detritus gravitational sinking rate,                       vsed        = ', vsed
961         WRITE(numout,*)     & 
962         &   ' coefficient for Martin et al. (1987) remineralisation,     xhr         = ', xhr
963!!
964!! Non-Medusa parameters
965         WRITE(numout,*) '=== Non-Medusa parameters'
966         WRITE(numout,*)     & 
967         &   ' time coeff of POC in sediments,                            sedlam      = ', sedlam
968         WRITE(numout,*)     &
969         &   ' Sediment geol loss for POC,                                sedlostpoc  = ', sedlostpoc
970         WRITE(numout,*)     &
971         &   ' Vert layer for diagnostic of vertical flux,                jpkp        = ', jpkb
972!!
973!! UKESM1 - new diagnostics  !! Jpalm
974         WRITE(numout,*) '=== UKESM1-related parameters'
975         WRITE(numout,*)     &
976         &   ' include DMS diagnostic?,                                   jdms        = ', jdms
977!!
978      ENDIF
979!!
980!! Key depth positions (with thanks to Andrew Coward for bug-fixing this bit)
981      DO jk = 1,jpk
982         !! level thickness
983         fthk  = e3t_1d(jk)
984         !! level depth (top of level)
985         fdep  = gdepw_1d(jk)
986         !! level depth (bottom of level)
987         fdep1 = fdep + fthk
988         !!
989         if (fdep.lt.100.0.AND.fdep1.gt.100.0) then        !  100 m
990            i0100 = jk
991         elseif (fdep.lt.150.0.AND.fdep1.gt.150.0) then    !  150 m (for BASIN)
992            i0150 = jk
993         elseif (fdep.lt.200.0.AND.fdep1.gt.200.0) then    !  200 m
994            i0200 = jk
995         elseif (fdep.lt.500.0.AND.fdep1.gt.500.0) then    !  500 m
996            i0500 = jk
997         elseif (fdep.lt.1000.0.AND.fdep1.gt.1000.0) then  ! 1000 m
998            i1000 = jk
999         elseif (fdep1.lt.1100.0) then                     ! 1100 m (for Moore et al. sedimentary iron)
1000            i1100 = jk
1001         endif
1002      enddo
1003      !!
1004      IF(lwp) THEN
1005          WRITE(numout,*) '=== Position of key depths'
1006          WRITE(numout,*)     & 
1007          &   ' jk position of  100 m horizon                              i0100       = ', i0100
1008          WRITE(numout,*)     &
1009          &   ' jk position of  150 m horizon                              i0150       = ', i0150
1010          WRITE(numout,*)     & 
1011          &   ' jk position of  200 m horizon                              i0200       = ', i0200
1012          WRITE(numout,*)     & 
1013          &   ' jk position of  500 m horizon                              i0500       = ', i0500
1014          WRITE(numout,*)     & 
1015          &   ' jk position of 1000 m horizon                              i1000       = ', i1000
1016          WRITE(numout,*)     & 
1017          &   ' jk position of 1100 m horizon [*]                          i1100       = ', i1100
1018          WRITE(numout,*) 'Got here ' , SIZE(friver_dep)
1019          CALL flush(numout)
1020      ENDIF
1021
1022#if defined key_roam
1023
1024      ! 1.4b namelist natroam : ROAM parameters
1025      ! ---------------------------------------
1026     
1027      xthetaphy = 0.
1028      xthetazoo = 0.
1029      xthetanit = 0.
1030      xthetarem = 0.
1031      xo2min    = 0.
1032
1033      !READ(numnatm,natroam)
1034         ! Namelist natbio
1035         ! -------------------
1036         REWIND( numnatp_ref )              ! Namelist nampisdia in reference namelist : Pisces diagnostics
1037         READ  ( numnatp_ref, natbio, IOSTAT = ios, ERR = 901)
1038901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in reference namelist', lwp )
1039
1040         REWIND( numnatp_cfg )              ! Namelist nampisdia in configuration namelist : Pisces diagnostics
1041         READ  ( numnatp_cfg, natbio, IOSTAT = ios, ERR = 902 )
1042902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in configuration namelist', lwp )
1043         IF(lwm) WRITE ( numonp, natbio )
1044
1045!! ROAM carbon, alkalinity and oxygen cycle parameters
1046!!       xthetaphy :  oxygen evolution/consumption by phytoplankton
1047!!       xthetazoo :  oxygen consumption by zooplankton
1048!!       xthetanit :  oxygen consumption by nitrogen remineralisation
1049!!       xthetarem :  oxygen consumption by carbon remineralisation
1050!!       xo2min    :  oxygen minimum concentration
1051
1052      IF(lwp) THEN
1053          WRITE(numout,*) 'natroam'
1054          WRITE(numout,*) ' '
1055!!
1056!! ROAM carbon, alkalinity and oxygen cycle parameters
1057          WRITE(numout,*) '=== ROAM carbon, alkalinity and oxygen cycle parameters'
1058          WRITE(numout,*)     &
1059          &   ' oxygen evolution/consumption by phytoplankton              xthetaphy   = ', xthetaphy
1060          WRITE(numout,*)     &
1061          &   ' oxygen consumption by zooplankton                          xthetazoo   = ', xthetazoo
1062          WRITE(numout,*)     &
1063          &   ' oxygen consumption by nitrogen remineralisation            xthetanit   = ', xthetanit
1064          WRITE(numout,*)     &
1065          &   ' oxygen consumption by carbon remineralisation              xthetarem   = ', xthetarem
1066          WRITE(numout,*)     &
1067          &   ' oxygen minimum concentration                               xo2min      = ', xo2min
1068       ENDIF
1069
1070#endif
1071
1072      CALL flush(numout)
1073
1074      ! 1.5 namelist natopt : parameters for optic
1075      ! ------------------------------------------
1076
1077      xkg0  = 0.
1078      xkr0  = 0.
1079      xkgp  = 0.
1080      xkrp  = 0.
1081      xlg   = 0.
1082      xlr   = 0.
1083      rpig  = 0.
1084
1085      !READ(numnatm,natopt)
1086         ! Namelist natopt
1087         ! -------------------
1088         REWIND( numnatp_ref )              ! Namelist nampisdia in reference namelist : Pisces diagnostics
1089         READ  ( numnatp_ref, natopt, IOSTAT = ios, ERR = 901)
1090901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in reference namelist', lwp )
1091
1092         REWIND( numnatp_cfg )              ! Namelist nampisdia in configuration namelist : Pisces diagnostics
1093         READ  ( numnatp_cfg, natopt, IOSTAT = ios, ERR = 902 )
1094902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nammeddia in configuration namelist', lwp )
1095         IF(lwm) WRITE ( numonp, natopt )
1096
1097      IF(lwp) THEN
1098         WRITE(numout,*) 'natopt'
1099         WRITE(numout,*) ' '
1100         WRITE(numout,*) ' green   water absorption coeff  xkg0  = ',xkg0
1101         WRITE(numout,*) ' red water absorption coeff      xkr0  = ',xkr0
1102         WRITE(numout,*) ' pigment red absorption coeff    xkrp  = ',xkrp
1103         WRITE(numout,*) ' pigment green absorption coeff  xkgp  = ',xkgp
1104         WRITE(numout,*) ' green chl exposant              xlg   = ',xlg
1105         WRITE(numout,*) ' red   chl exposant              xlr   = ',xlr
1106         WRITE(numout,*) ' chla/chla+phea ratio            rpig  = ',rpig
1107         WRITE(numout,*) ' '
1108
1109      ENDIF
1110
1111      IF(lwp) THEN
1112         WRITE(numout,*) 'NaN check'
1113         WRITE(numout,*) ' '
1114         q1 = -1.
1115         q2 = 0.
1116         q3 = log(q1)
1117         write (numout,*) 'q3 = ', q3
1118         if ( ieee_is_nan( q3 ) ) then
1119            write (numout,*) 'NaN detected'
1120         else
1121            write (numout,*) 'NaN not detected'
1122         endif
1123         WRITE(numout,*) ' '
1124       ENDIF
1125
1126   END SUBROUTINE trc_nam_medusa
1127   
1128#else
1129   !!----------------------------------------------------------------------
1130   !!  Dummy module :                                             No MEDUSA
1131   !!----------------------------------------------------------------------
1132CONTAINS
1133   SUBROUTINE trc_nam_medusa                      ! Empty routine
1134   END  SUBROUTINE  trc_nam_medusa
1135#endif 
1136
1137   !!======================================================================
1138END MODULE trcnam_medusa
Note: See TracBrowser for help on using the repository browser.