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.
trcbio_medusa.F90 in branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcbio_medusa.F90 @ 7920

Last change on this file since 7920 was 7920, checked in by marc, 7 years ago

Removing the finalisation of diagnostics from trcbio_medusa.F90 into bio_medusa_fin.F90

File size: 245.2 KB
Line 
1MODULE trcbio_medusa
2   !!======================================================================
3   !!                         ***  MODULE trcbio  ***
4   !! TOP :   MEDUSA
5   !!======================================================================
6   !! History :
7   !!  -   !  1999-07  (M. Levy)              original code
8   !!  -   !  2000-12  (E. Kestenare)         assign parameters to name individual tracers
9   !!  -   !  2001-03  (M. Levy)              LNO3 + dia2d
10   !! 2.0  !  2007-12  (C. Deltel, G. Madec)  F90
11   !!  -   !  2008-08  (K. Popova)            adaptation for MEDUSA
12   !!  -   !  2008-11  (A. Yool)              continuing adaptation for MEDUSA
13   !!  -   !  2010-03  (A. Yool)              updated for branch inclusion
14   !!  -   !  2011-08  (A. Yool)              updated for ROAM (see below)
15   !!  -   !  2013-03  (A. Yool)              updated for iMARNET
16   !!  -   !  2013-05  (A. Yool)              updated for v3.5
17   !!  -   !  2014-08  (A. Yool, J. Palm)     Add DMS module for UKESM1 model
18   !!  -   !  2015-06  (A. Yool)              Update to include MOCSY
19   !!  -   !  2015-07  (A. Yool)              Update for rolling averages
20   !!  -   !  2015-10  (J. Palm)              Update for diag outputs through iom_use 
21   !!  -   !  2016-11  (A. Yool)              Updated diags for CMIP6
22   !!----------------------------------------------------------------------
23   !!
24#if defined key_roam
25   !!----------------------------------------------------------------------
26   !! Updates for the ROAM project include:
27   !!   - addition of DIC, alkalinity, detrital carbon and oxygen tracers
28   !!   - addition of air-sea fluxes of CO2 and oxygen
29   !!   - periodic (monthly) calculation of full 3D carbonate chemistry
30   !!   - detrital C:N ratio now free to evolve dynamically
31   !!   - benthic storage pools
32   !!
33   !! Opportunity also taken to add functionality:
34   !!   - switch for Liebig Law (= most-limiting) nutrient uptake
35   !!   - switch for accelerated seafloor detritus remineralisation
36   !!   - switch for fast -> slow detritus transfer at seafloor
37   !!   - switch for ballast vs. Martin vs. Henson fast detritus remin.
38   !!   - per GMD referee remarks, xfdfrac3 introduced for grazed PDS
39   !!----------------------------------------------------------------------
40#endif
41   !!
42#if defined key_mocsy
43   !!----------------------------------------------------------------------
44   !! Updates with the addition of MOCSY include:
45   !!   - option to use PML or MOCSY carbonate chemistry (the latter is
46   !!     preferred)
47   !!   - central calculation of gas transfer velocity, f_kw660; previously
48   !!     this was done separately for CO2 and O2 with predictable results
49   !!   - distribution of f_kw660 to both PML and MOCSY CO2 air-sea flux
50   !!     calculations and to those for O2 air-sea flux
51   !!   - extra diagnostics included for MOCSY
52   !!----------------------------------------------------------------------
53#endif
54   !!
55#if defined key_medusa
56   !!----------------------------------------------------------------------
57   !!                                        MEDUSA bio-model
58   !!----------------------------------------------------------------------
59   !!   trc_bio_medusa        : 
60   !!----------------------------------------------------------------------
61      USE oce_trc
62      USE trc
63      USE sms_medusa
64      USE lbclnk
65      USE prtctl_trc      ! Print control for debugging
66      USE trcsed_medusa
67      USE sbc_oce         ! surface forcing
68      USE sbcrnf          ! surface boundary condition: runoff variables
69      USE in_out_manager  ! I/O manager
70# if defined key_iomput
71      USE iom
72      USE trcnam_medusa         ! JPALM 13-11-2015 -- if iom_use for diag
73      !!USE trc_nam_iom_medusa  ! JPALM 13-11-2015 -- if iom_use for diag
74# endif
75# if defined key_roam
76      USE gastransfer
77#  if defined key_mocsy
78      USE mocsy_wrapper
79#  else
80      USE trcco2_medusa
81#  endif
82      USE trcoxy_medusa
83      !! Jpalm (08/08/2014)
84      USE trcdms_medusa
85# endif
86      !! AXY (18/01/12): brought in for benthic timestepping
87      USE trcnam_trp      ! AXY (24/05/2013)
88      USE trdmxl_trc
89      USE trdtrc_oce  ! AXY (24/05/2013)
90
91      !! AXY (30/01/14): necessary to find NaNs on HECTOR
92      USE, INTRINSIC :: ieee_arithmetic 
93
94      !! JPALM (27-06-2016): add lk_oasis for CO2 and DMS coupling with atm
95      USE sbc_oce,                ONLY: lk_oasis
96      USE oce,                    ONLY: CO2Flux_out_cpl, DMS_out_cpl,       &
97                                        PCO2a_in_cpl
98      USE bio_medusa_mod
99      USE bio_medusa_init_mod,    ONLY: bio_medusa_init
100      USE bio_medusa_fin_mod,     ONLY: bio_medusa_fin
101
102      IMPLICIT NONE
103      PRIVATE
104     
105      PUBLIC   trc_bio_medusa    ! called in trcsms_medusa.F90
106
107   !!* Substitution
108#  include "domzgr_substitute.h90"
109   !!----------------------------------------------------------------------
110   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
111   !! $Id$
112   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
113   !!----------------------------------------------------------------------
114
115CONTAINS
116
117   SUBROUTINE trc_bio_medusa( kt )
118      !!---------------------------------------------------------------------
119      !!                     ***  ROUTINE trc_bio  ***
120      !!
121      !! ** Purpose :   compute the now trend due to biogeochemical processes
122      !!              and add it to the general trend of passive tracers equations
123      !!
124      !! ** Method  :   each now biological flux is calculated in function of now
125      !!              concentrations of tracers.
126      !!              depending on the tracer, these fluxes are sources or sinks.
127      !!              the total of the sources and sinks for each tracer
128      !!              is added to the general trend.
129      !!       
130      !!                      tra = tra + zf...tra - zftra...
131      !!                                     |         |
132      !!                                     |         |
133      !!                                  source      sink
134      !!       
135      !!              IF 'key_trc_diabio' defined , the biogeochemical trends
136      !!              for passive tracers are saved for futher diagnostics.
137      !!---------------------------------------------------------------------
138      !!
139      !!
140      !!----------------------------------------------------------------------           
141      !! Variable conventions
142      !!----------------------------------------------------------------------
143      !!
144      !! names: z*** - state variable
145      !!        f*** - function (or temporary variable used in part of a function)
146      !!        x*** - parameter
147      !!        b*** - right-hand part (sources and sinks)
148      !!        i*** - integer variable (usually used in yes/no flags)
149      !!
150      !! time (integer timestep)
151      INTEGER, INTENT( in ) ::    kt
152      !!
153      !! spatial array indices
154      INTEGER  ::    ji,jj,jk,jn
155      !!
156      !! AXY (27/07/10): add in indices for depth horizons (for sinking flux
157      !!                 and seafloor iron inputs)
158      !! INTEGER  ::    i0100, i0200, i0500, i1000, i1100
159      !!
160      !! model state variables
161      REAL(wp), DIMENSION(jpi,jpj) ::    zchn,zchd,zphn,zphd,zpds,zzmi
162      REAL(wp), DIMENSION(jpi,jpj) ::    zzme,zdet,zdtc,zdin,zsil,zfer
163      REAL(wp) ::    zage
164# if defined key_roam
165      REAL(wp), DIMENSION(jpi,jpj) ::    zdic, zalk, zoxy
166      REAL(wp), DIMENSION(jpi,jpj) ::    ztmp, zsal
167# endif
168# if defined key_mocsy
169      REAL(wp), DIMENSION(jpi,jpj) ::    zpho
170# endif
171      !!
172      !! integrated source and sink terms
173      REAL(wp) ::    b0
174      !! AXY (23/08/13): changed from individual variables for each flux to
175      !!                 an array that holds all fluxes
176      REAL(wp), DIMENSION(jpi,jpj,jp_medusa) ::    btra
177      !!
178      !! primary production and chl related quantities     
179      REAL(wp), DIMENSION(jpi,jpj) ::    fthetan,faln,fchn1,fchn,fjln,fprn,frn
180      REAL(wp), DIMENSION(jpi,jpj) ::    fthetad,fald,fchd1,fchd,fjld,fprd,frd
181      !! AXY (23/11/16): add in light-only limitation term (normalised 0-1 range)
182      REAL(wp), DIMENSION(jpi,jpj) ::    fjlim_pn, fjlim_pd
183      !! AXY (03/02/11): add in Liebig terms
184      REAL(wp), DIMENSION(jpi,jpj) ::    fpnlim, fpdlim
185      !! AXY (16/07/09): add in Eppley curve functionality
186      REAL(wp), DIMENSION(jpi,jpj) ::    fun_T,xvpnT,xvpdT
187      INTEGER  ::    ieppley
188      !! AXY (16/05/11): per Katya's prompting, add in new T-dependence
189      !!                 for phytoplankton growth only (i.e. no change
190      !!                 for remineralisation)
191      REAL(wp), DIMENSION(jpi,jpj) ::    fun_Q10
192      !! AXY (01/03/10): add in mixed layer PP diagnostics
193!      REAL(wp), DIMENSION(jpi,jpj) ::    fprn_ml,fprd_ml
194      !!
195      !! nutrient limiting factors
196      REAL(wp), DIMENSION(jpi,jpj) ::    fnln,ffln            !! N and Fe
197      REAL(wp), DIMENSION(jpi,jpj) ::    fnld,ffld,fsld,fsld2 !! N, Fe and Si
198      !!
199      !! silicon cycle
200      REAL(wp), DIMENSION(jpi,jpj) ::    fsin,fnsi,fprds,fsdiss
201      REAL(wp)                     ::    fsin1,fnsi1,fnsi2
202      !!
203      !! iron cycle; includes parameters for Parekh et al. (2005) iron scheme
204      REAL(wp), DIMENSION(jpi,jpj) ::    ffetop,ffebot,ffescav
205      REAL(wp) ::    xLgF, xFeT, xFeF, xFeL         !! state variables for iron-ligand system
206!      REAL(wp), DIMENSION(jpi,jpj) ::  xFree        !! state variables for iron-ligand system
207      REAL(wp) ::    xb_coef_tmp, xb2M4ac           !! iron-ligand parameters
208      REAL(wp) ::    xmaxFeF,fdeltaFe               !! max Fe' parameters
209      !!
210      !! local parameters for Moore et al. (2004) alternative scavenging scheme
211      REAL(wp) ::    fbase_scav,fscal_sink,fscal_part,fscal_scav
212      !!
213      !! local parameters for Moore et al. (2008) alternative scavenging scheme
214      REAL(wp) ::    fscal_csink,fscal_sisink,fscal_casink
215      !!
216      !! local parameters for Galbraith et al. (2010) alternative scavenging scheme
217      REAL(wp) ::    xCscav1, xCscav2, xk_org, xORGscav  !! organic portion of scavenging
218      REAL(wp) ::    xk_inorg, xINORGscav                !! inorganic portion of scavenging
219      !!
220      !! microzooplankton grazing
221      REAL(wp), DIMENSION(jpi,jpj) ::    fmi1,fmi,fgmipn,fgmid,fgmidc
222      REAL(wp), DIMENSION(jpi,jpj) ::    finmi,ficmi,fstarmi,fmith,fmigrow,fmiexcr,fmiresp
223      !!
224      !! mesozooplankton grazing
225      REAL(wp), DIMENSION(jpi,jpj) ::    fme1,fme,fgmepn,fgmepd,fgmepds,fgmezmi,fgmed,fgmedc
226      REAL(wp), DIMENSION(jpi,jpj) ::    finme,ficme,fstarme,fmeth,fmegrow,fmeexcr,fmeresp
227      !!
228      !! mortality/Remineralisation (defunct parameter "fz" removed)
229      REAL(wp), DIMENSION(jpi,jpj) ::    fdpn,fdpd,fdpds,fdzmi,fdzme,fdd
230# if defined key_roam
231      REAL(wp), DIMENSION(jpi,jpj) ::    fddc
232# endif
233      REAL(wp), DIMENSION(jpi,jpj) ::    fdpn2,fdpd2,fdpds2,fdzmi2,fdzme2
234      REAL(wp), DIMENSION(jpi,jpj) ::    fslown, fslowc
235      REAL(wp), DIMENSION(jpi,jpj) ::    fslownflux, fslowcflux
236      REAL(wp), DIMENSION(jpi,jpj) ::    fregen,fregensi
237!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenfast,fregenfastsi
238# if defined key_roam
239!! Doesn't look like this is used - marc 10/4/17
240!!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenc
241!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenfastc
242# endif
243      !!
244      !! particle flux
245      REAL(WP), DIMENSION(jpi,jpj) ::    fdep1,fcaco3
246      REAL(WP), DIMENSION(jpi,jpj) ::    ftempn,ftempsi,ftempfe,ftempc,ftempca
247      REAL(wp), DIMENSION(jpi,jpj) ::    freminn,freminsi,freminfe,freminc,freminca
248!      REAL(wp), DIMENSION(jpi,jpj) ::    ffastn,ffastsi,ffastfe,ffastc,ffastca
249      REAL(wp), DIMENSION(jpi,jpj) ::    fprotf
250!      REAL(wp), DIMENSION(jpi,jpj) ::    fsedn,fsedsi,fsedfe,fsedc,fsedca
251!      REAL(wp), DIMENSION(jpi,jpj) ::    fccd
252      REAL(wp), DIMENSION(jpi,jpj) ::    fccd_dep
253      !!
254      !! AXY (06/07/11): alternative fast detritus schemes
255      REAL(wp) ::    fb_val, fl_sst
256      !!
257      !! AXY (08/07/11): fate of fast detritus reaching the seafloor
258! I don't think ffast2slowfe is used - marc 10/4/17
259!      REAL(wp), DIMENSION(jpi,jpj) ::    ffast2slown,ffast2slowfe,ffast2slowc
260      REAL(wp), DIMENSION(jpi,jpj) ::    ffast2slown,ffast2slowc
261      !!
262      !! conservation law
263      REAL(wp) ::    fnit0,fsil0,ffer0 
264# if defined key_roam
265      REAL(wp) ::    fcar0,falk0,foxy0 
266# endif     
267      !!
268      !! temporary variables
269      REAL(wp) ::    fq0,fq1,fq2,fq3,fq4,fq5,fq6,fq7,fq8,fq9
270      !!
271      !! water column nutrient and flux integrals
272!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_n,ftot_si,ftot_fe
273!      REAL(wp), DIMENSION(jpi,jpj) ::    fflx_n,fflx_si,fflx_fe
274!      REAL(wp), DIMENSION(jpi,jpj) ::    fifd_n,fifd_si,fifd_fe
275!      REAL(wp), DIMENSION(jpi,jpj) ::    fofd_n,fofd_si,fofd_fe
276# if defined key_roam
277!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_c,ftot_a,ftot_o2
278!      REAL(wp), DIMENSION(jpi,jpj) ::    fflx_c,fflx_a,fflx_o2
279!      REAL(wp), DIMENSION(jpi,jpj) ::    fifd_c,fifd_a,fifd_o2
280!      REAL(wp), DIMENSION(jpi,jpj) ::    fofd_c,fofd_a,fofd_o2
281# endif
282      !!
283      !! zooplankton grazing integrals
284!      REAL(wp), DIMENSION(jpi,jpj) ::    fzmi_i,fzmi_o,fzme_i,fzme_o
285      !!
286      !! limitation term temporary variables
287!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_pn,ftot_pd
288!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_zmi,ftot_zme,ftot_det,ftot_dtc
289      !! use ballast scheme (1) or simple exponential scheme (0; a conservation test)
290      INTEGER  ::    iball
291      !! use biological fluxes (1) or not (0)
292      INTEGER  ::    ibio_switch
293      !!
294      !! diagnose fluxes (should only be used in 1D runs)
295      INTEGER  ::    idf, idfval
296      !!
297      !! nitrogen and silicon production and consumption
298      REAL(wp) ::    fn_prod, fn_cons, fs_prod, fs_cons
299!      REAL(wp), DIMENSION(jpi,jpj) ::    fnit_prod, fnit_cons, fsil_prod, fsil_cons
300# if defined key_roam
301      !!
302      !! flags to help with calculating the position of the CCD
303      INTEGER, DIMENSION(jpi,jpj) ::     i2_omcal,i2_omarg
304      !!
305      !! AXY (24/11/16): add xCO2 variable for atmosphere (what we actually have)
306      REAL(wp)                     ::    f_xco2a
307      REAL(wp), DIMENSION(jpi,jpj) ::    f_ph, f_pco2w, f_h2co3, f_hco3, f_co3, f_co2flux
308      REAL(wp), DIMENSION(jpi,jpj) ::    f_TDIC, f_TALK, f_dcf, f_henry
309      REAL(wp), DIMENSION(jpi,jpj) ::    f_pp0
310      REAL(wp), DIMENSION(jpi,jpj) ::    f_kw660, f_o2flux, f_o2sat
311      REAL(wp)                     ::    f_o2sat3
312!      REAL(wp), DIMENSION(jpi,jpj) ::    f_omcal, f_omarg
313      !!
314      !! AXY (23/06/15): additional diagnostics for MOCSY and oxygen
315      REAL(wp), DIMENSION(jpi,jpj) ::    f_fco2w, f_BetaD, f_rhosw, f_opres, f_insitut, f_pco2atm, f_fco2atm
316      REAL(wp), DIMENSION(jpi,jpj) ::    f_schmidtco2, f_kwco2, f_K0, f_co2starair, f_dpco2, f_kwo2
317      !! jpalm 14-07-2016: convert CO2flux diag from mmol/m2/d to kg/m2/s
318      REAL, PARAMETER :: weight_CO2_mol = 44.0095  !! g / mol
319      REAL, PARAMETER :: secs_in_day    = 86400.0  !! s / d
320      REAL, PARAMETER :: CO2flux_conv   = (1.e-6 * weight_CO2_mol) / secs_in_day
321
322      !!
323      INTEGER, DIMENSION(jpi,jpj)  ::    iters
324      REAL(wp) ::    f_year
325      INTEGER  ::    i_year
326      INTEGER  ::    iyr1, iyr2
327      !!
328      !! carbon, alkalinity production and consumption
329      REAL(wp) ::    fc_prod, fc_cons, fa_prod, fa_cons
330!      REAL(wp), DIMENSION(jpi,jpj) ::    fcomm_resp
331!      REAL(wp), DIMENSION(jpi,jpj) ::    fcar_prod, fcar_cons
332      !!
333      !! oxygen production and consumption (and non-consumption)
334      REAL(wp), DIMENSION(jpi,jpj) ::    fo2_prod, fo2_cons, fo2_ncons, fo2_ccons
335!      REAL(wp), DIMENSION(jpi,jpj) ::    foxy_prod, foxy_cons, foxy_anox
336      !! Jpalm (11-08-2014)
337      !! add DMS in MEDUSA for UKESM1 model
338      REAL(wp), DIMENSION(jpi,jpj) ::    dms_surf
339      !! AXY (13/03/15): add in other DMS calculations
340      REAL(wp), DIMENSION(jpi,jpj) ::    dms_andr, dms_simo, dms_aran, dms_hall
341
342# endif
343      !!
344      !! benthic fluxes
345!      INTEGER  ::    ibenthic
346!      REAL(wp), DIMENSION(jpi,jpj) :: f_sbenin_n, f_sbenin_fe,              f_sbenin_c
347!      REAL(wp), DIMENSION(jpi,jpj) :: f_fbenin_n, f_fbenin_fe, f_fbenin_si, f_fbenin_c, f_fbenin_ca
348!      REAL(wp), DIMENSION(jpi,jpj) :: f_benout_n, f_benout_fe, f_benout_si, f_benout_c, f_benout_ca
349      REAL(wp) ::    zfact
350      !!
351      !! benthic fluxes of CaCO3 that shouldn't happen because of lysocline
352!      REAL(wp), DIMENSION(jpi,jpj) :: f_benout_lyso_ca
353      !!
354      !! riverine fluxes
355!      REAL(wp), DIMENSION(jpi,jpj) :: f_runoff, f_riv_n, f_riv_si, f_riv_c, f_riv_alk
356      !! AXY (19/07/12): variables for local riverine fluxes to handle inputs below surface
357      REAL(wp), DIMENSION(jpi,jpj) :: f_riv_loc_n, f_riv_loc_si, f_riv_loc_c, f_riv_loc_alk
358      !!---------------------------------------------------------------------
359
360# if defined key_debug_medusa
361      IF (lwp) write (numout,*) 'trc_bio_medusa: variables defined'
362      CALL flush(numout)
363# endif 
364
365      !! AXY (20/11/14): alter this to report on first MEDUSA call
366      !! IF( kt == nit000 ) THEN
367      IF( kt == nittrc000 ) THEN
368         IF(lwp) WRITE(numout,*)
369         IF(lwp) WRITE(numout,*) ' trc_bio: MEDUSA bio-model'
370         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
371    IF(lwp) WRITE(numout,*) ' kt =',kt
372      ENDIF
373
374      !! AXY (13/01/12): is benthic model properly interactive? 0 = no, 1 = yes
375      ibenthic = 1
376
377      !! not sure what this is for; it's not used anywhere; commenting out
378      !! fbodn(:,:) = 0.e0   
379
380      !!
381      IF( ln_diatrc ) THEN
382         !! blank 2D diagnostic array
383         trc2d(:,:,:) = 0.e0
384         !!
385         !! blank 3D diagnostic array
386         trc3d(:,:,:,:) = 0.e0
387      ENDIF
388
389      !!----------------------------------------------------------------------
390      !! b0 is present for debugging purposes; using b0 = 0 sets the tendency
391      !! terms of all biological equations to 0.
392      !!----------------------------------------------------------------------
393      !!
394      !! AXY (03/09/14): probably not the smartest move ever, but it'll fit
395      !!                 the bill for now; another item on the things-to-sort-
396      !!     out-in-the-future list ...
397# if defined key_kill_medusa
398      b0 = 0.
399# else
400      b0 = 1.
401# endif
402      !!----------------------------------------------------------------------
403      !! fast detritus ballast scheme (0 = no; 1 = yes)
404      !! alternative to ballast scheme is same scheme but with no ballast
405      !! protection (not dissimilar to Martin et al., 1987)
406      !!----------------------------------------------------------------------
407      !!
408      iball = 1
409
410      !!----------------------------------------------------------------------
411      !! full flux diagnostics (0 = no; 1 = yes); appear in ocean.output
412      !! these should *only* be used in 1D since they give comprehensive
413      !! output for ecological functions in the model; primarily used in
414      !! debugging
415      !!----------------------------------------------------------------------
416      !!
417      idf    = 0
418      !!
419      !! timer mechanism
420      if (kt/120*120.eq.kt) then
421         idfval = 1
422      else
423         idfval = 0
424      endif
425
426      !!----------------------------------------------------------------------
427      !! Initialise arrays to zero and set up arrays for diagnostics
428      !!----------------------------------------------------------------------
429! tmp - marc
430      write(numout,*) 'bbb13. before call to bio_medusa_init,kt=',kt
431      flush(numout)
432!
433      CALL bio_medusa_init( kt )
434! tmp - marc
435      write(numout,*) 'bbb14. after call to bio_medusa_init,kt=',kt
436      flush(numout)
437!
438       !!
439# if defined key_axy_nancheck
440       DO jn = 1,jptra
441          !! fq0 = MINVAL(trn(:,:,:,jn))
442          !! fq1 = MAXVAL(trn(:,:,:,jn))
443          fq2 = SUM(trn(:,:,:,jn))
444          !! if (lwp) write (numout,'(a,2i6,3(1x,1pe15.5))') 'NAN-CHECK', &
445          !! &        kt, jn, fq0, fq1, fq2
446          !! AXY (30/01/14): much to our surprise, the next line doesn't work on HECTOR
447          !!                 and has been replaced here with a specialist routine
448          !! if (fq2 /= fq2 ) then
449          if ( ieee_is_nan( fq2 ) ) then
450             !! there's a NaN here
451             if (lwp) write(numout,*) 'NAN detected in field', jn, 'at time', kt, 'at position:'
452             DO jk = 1,jpk
453                DO jj = 1,jpj
454                   DO ji = 1,jpi
455                      !! AXY (30/01/14): "isnan" problem on HECTOR
456                      !! if (trn(ji,jj,jk,jn) /= trn(ji,jj,jk,jn)) then
457                      if ( ieee_is_nan( trn(ji,jj,jk,jn) ) ) then
458                         if (lwp) write (numout,'(a,1pe12.2,4i6)') 'NAN-CHECK', &
459                         &        tmask(ji,jj,jk), ji, jj, jk, jn
460                      endif
461                   enddo
462                enddo
463             enddo
464             CALL ctl_stop( 'trcbio_medusa, NAN in incoming tracer field' )
465          endif
466       ENDDO
467       CALL flush(numout)
468# endif
469
470# if defined key_debug_medusa
471      IF (lwp) write (numout,*) 'trc_bio_medusa: variables initialised and checked'
472      CALL flush(numout)
473# endif 
474
475# if defined key_roam
476      !!----------------------------------------------------------------------
477      !! calculate atmospheric pCO2
478      !!----------------------------------------------------------------------
479      !!
480      !! what's atmospheric pCO2 doing? (data start in 1859)
481      iyr1  = nyear - 1859 + 1
482      iyr2  = iyr1 + 1
483      if (iyr1 .le. 1) then
484         !! before 1860
485         f_xco2a = hist_pco2(1)
486      elseif (iyr2 .ge. 242) then
487         !! after 2099
488         f_xco2a = hist_pco2(242)
489      else
490         !! just right
491         fq0 = hist_pco2(iyr1)
492         fq1 = hist_pco2(iyr2)
493         fq2 = real(nsec_day) / (60.0 * 60.0 * 24.0)
494         !! AXY (14/06/12): tweaked to make more sense (and be correct)
495#  if defined key_bs_axy_yrlen
496         fq3 = (real(nday_year) - 1.0 + fq2) / 360.0  !! bugfix: for 360d year with HadGEM2-ES forcing
497#  else
498         fq3 = (real(nday_year) - 1.0 + fq2) / 365.0  !! original use of 365 days (not accounting for leap year or 360d year)
499#  endif
500         fq4 = (fq0 * (1.0 - fq3)) + (fq1 * fq3)
501         f_xco2a = fq4
502      endif
503#  if defined key_axy_pi_co2
504      f_xco2a = 284.725          !! OCMIP pre-industrial pCO2
505#  endif
506      !! IF(lwp) WRITE(numout,*) ' MEDUSA nyear     =', nyear
507      !! IF(lwp) WRITE(numout,*) ' MEDUSA nsec_day  =', real(nsec_day)
508      !! IF(lwp) WRITE(numout,*) ' MEDUSA nday_year =', real(nday_year)
509      !! AXY (29/01/14): remove surplus diagnostics
510      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq0       =', fq0
511      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq1       =', fq1
512      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq2       =', fq2
513      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq3       =', fq3
514      IF(lwp) WRITE(numout,*) ' MEDUSA atm pCO2  =', f_xco2a
515# endif
516
517# if defined key_debug_medusa
518      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for carbonate chemistry'
519      IF (lwp) write (numout,*) 'trc_bio_medusa: kt = ', kt
520      IF (lwp) write (numout,*) 'trc_bio_medusa: nittrc000 = ', nittrc000
521      CALL flush(numout)
522# endif 
523
524# if defined key_roam
525      !! AXY (20/11/14): alter to call on first MEDUSA timestep and then every
526      !!                 month (this is hardwired as 960 timesteps but should
527      !!                 be calculated and done properly
528      !! IF( kt == nit000 .or. mod(kt,1920) == 0 ) THEN
529      !! IF( kt == nittrc000 .or. mod(kt,960) == 0 ) THEN
530      !!=============================
531      !! Jpalm -- 07-10-2016 -- need to change carb-chem frequency call :
532      !!          we don't want to call on the first time-step of all run submission,
533      !!          but only on the very first time-step, and then every month
534      !!          So we call on nittrc000 if not restarted run,
535      !!          else if one month after last call.
536      !!          assume one month is 30d --> 3600*24*30 : 2592000s
537      !!          try to call carb-chem at 1st month's tm-stp : x * 30d + 1*rdt(i.e: mod = rdt)   
538      !!          ++ need to pass carb-chem output var through restarts
539      If ( ( kt == nittrc000 .AND. .NOT.ln_rsttr ) .OR. mod(kt*rdt,2592000.) == rdt ) THEN
540         !!----------------------------------------------------------------------
541         !! Calculate the carbonate chemistry for the whole ocean on the first
542         !! simulation timestep and every month subsequently; the resulting 3D
543         !! field of omega calcite is used to determine the depth of the CCD
544         !!----------------------------------------------------------------------
545         !!
546         IF(lwp) WRITE(numout,*) ' MEDUSA calculating all carbonate chemistry at kt =', kt
547         CALL flush(numout)
548         !! blank flags
549         i2_omcal(:,:) = 0
550         i2_omarg(:,:) = 0
551         !! loop over 3D space
552         DO jk = 1,jpk
553            DO jj = 2,jpjm1
554               DO ji = 2,jpim1
555                  !! OPEN wet point IF..THEN loop
556                  if (tmask(ji,jj,jk).eq.1) then
557                     IF (lk_oasis) THEN
558                        f_xco2a = PCO2a_in_cpl(ji,jj)        !! use 2D atm xCO2 from atm coupling
559                     ENDIF
560                     !! do carbonate chemistry
561                     !!
562                     !! set up required state variables
563                     zdic(ji,jj) = max(0.,trn(ji,jj,jk,jpdic)) !! dissolved inorganic carbon
564                     zalk(ji,jj) = max(0.,trn(ji,jj,jk,jpalk)) !! alkalinity
565                     ztmp(ji,jj) = tsn(ji,jj,jk,jp_tem)        !! temperature
566                     zsal(ji,jj) = tsn(ji,jj,jk,jp_sal)        !! salinity
567#  if defined key_mocsy
568                     zsil(ji,jj) = max(0.,trn(ji,jj,jk,jpsil))        !! silicic acid
569                     zpho(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) / 16.0 !! phosphate via DIN and Redfield
570#  endif
571           !!
572           !! AXY (28/02/14): check input fields
573           if (ztmp(ji,jj) .lt. -3.0 .or. ztmp(ji,jj) .gt. 40.0 ) then
574                        IF(lwp) WRITE(numout,*) ' trc_bio_medusa: T WARNING 3D, ', &
575                        tsb(ji,jj,jk,jp_tem), tsn(ji,jj,jk,jp_tem), ' at (',    &
576                        ji, ',', jj, ',', jk, ') at time', kt
577         IF(lwp) WRITE(numout,*) ' trc_bio_medusa: T SWITCHING 3D, ', &
578         tsn(ji,jj,jk,jp_tem), ' -> ', tsb(ji,jj,jk,jp_tem)
579                        ztmp(ji,jj) = tsb(ji,jj,jk,jp_tem)     !! temperature
580                     endif
581           if (zsal(ji,jj) .lt. 0.0 .or. zsal(ji,jj) .gt. 45.0 ) then
582                        IF(lwp) WRITE(numout,*) ' trc_bio_medusa: S WARNING 3D, ', &
583                        tsb(ji,jj,jk,jp_sal), tsn(ji,jj,jk,jp_sal), ' at (',    &
584                        ji, ',', jj, ',', jk, ') at time', kt
585                     endif
586                     !!
587                     !! blank input variables not used at this stage (they relate to air-sea flux)
588                     f_kw660(ji,jj) = 1.0
589                     f_pp0(ji,jj)   = 1.0
590                     !!
591                     !! calculate carbonate chemistry at grid cell midpoint
592#  if defined key_mocsy
593                     !! AXY (22/06/15): use Orr & Epitalon (2015) MOCSY-2 carbonate
594                     !!                 chemistry package
595                     CALL mocsy_interface( ztmp(ji,jj), zsal(ji,jj), zalk(ji,jj), zdic(ji,jj), zsil(ji,jj), zpho(ji,jj),         &    ! inputs
596                     f_pp0(ji,jj), fsdept(ji,jj,jk), gphit(ji,jj), f_kw660(ji,jj), f_xco2a, 1,                  &    ! inputs
597                     f_ph(ji,jj), f_pco2w(ji,jj), f_fco2w(ji,jj), f_h2co3(ji,jj), f_hco3(ji,jj), f_co3(ji,jj), f_omarg(ji,jj),   &    ! outputs
598                     f_omcal(ji,jj), f_BetaD(ji,jj), f_rhosw(ji,jj), f_opres(ji,jj), f_insitut(ji,jj),             &    ! outputs
599                     f_pco2atm(ji,jj), f_fco2atm(ji,jj), f_schmidtco2(ji,jj), f_kwco2(ji,jj), f_K0(ji,jj),                &    ! outputs
600                     f_co2starair(ji,jj), f_co2flux(ji,jj), f_dpco2(ji,jj) )                                     ! outputs
601                     !!
602                     f_TDIC(ji,jj) = (zdic(ji,jj) / f_rhosw(ji,jj)) * 1000. ! mmol / m3 -> umol / kg
603                     f_TALK(ji,jj) = (zalk(ji,jj) / f_rhosw(ji,jj)) * 1000. !  meq / m3 ->  ueq / kg
604                     f_dcf(ji,jj)  = f_rhosw(ji,jj)
605#  else
606                     !! AXY (22/06/15): use old PML carbonate chemistry package (the
607                     !!                 MEDUSA-2 default)
608                     CALL trc_co2_medusa( ztmp(ji,jj), zsal(ji,jj), zdic(ji,jj), zalk(ji,jj), fsdept(ji,jj,jk), f_kw660(ji,jj),      &    ! inputs
609                     f_xco2a, f_ph(ji,jj), f_pco2w(ji,jj), f_h2co3(ji,jj), f_hco3(ji,jj), f_co3(ji,jj), f_omcal(ji,jj),   &    ! outputs
610                     f_omarg(ji,jj), f_co2flux(ji,jj), f_TDIC(ji,jj), f_TALK(ji,jj), f_dcf(ji,jj), f_henry(ji,jj), iters(ji,jj))      ! outputs
611                     !!
612                     !! AXY (28/02/14): check output fields
613                     if (iters(ji,jj) .eq. 25) then
614                        IF(lwp) WRITE(numout,*) ' trc_bio_medusa: 3D ITERS WARNING, ', &
615                        iters(ji,jj), ' AT (', ji, ', ', jj, ', ', jk, ') AT ', kt
616                     endif
617#  endif
618                     !!
619                     !! store 3D outputs
620                     f3_pH(ji,jj,jk)    = f_ph(ji,jj)
621                     f3_h2co3(ji,jj,jk) = f_h2co3(ji,jj)
622                     f3_hco3(ji,jj,jk)  = f_hco3(ji,jj)
623                     f3_co3(ji,jj,jk)   = f_co3(ji,jj)
624                     f3_omcal(ji,jj,jk) = f_omcal(ji,jj)
625                     f3_omarg(ji,jj,jk) = f_omarg(ji,jj)
626                     !!
627                     !! CCD calculation: calcite
628                     if (i2_omcal(ji,jj) .eq. 0 .and. f_omcal(ji,jj) .lt. 1.0) then
629                        if (jk .eq. 1) then
630                           f2_ccd_cal(ji,jj) = fsdept(ji,jj,jk)
631                        else
632                           fq0 = f3_omcal(ji,jj,jk-1) - f_omcal(ji,jj)
633                           fq1 = f3_omcal(ji,jj,jk-1) - 1.0
634                           fq2 = fq1 / (fq0 + tiny(fq0))
635                           fq3 = fsdept(ji,jj,jk) - fsdept(ji,jj,jk-1)
636                           fq4 = fq2 * fq3
637                           f2_ccd_cal(ji,jj) = fsdept(ji,jj,jk-1) + fq4
638                        endif
639                        i2_omcal(ji,jj)   = 1
640                     endif
641                     if ( i2_omcal(ji,jj) .eq. 0 .and. jk .eq. mbathy(ji,jj) ) then
642                        !! reached seafloor and still no dissolution; set to seafloor (W-point)
643                        f2_ccd_cal(ji,jj) = fsdepw(ji,jj,jk+1)
644                        i2_omcal(ji,jj)   = 1
645                     endif
646                     !!
647                     !! CCD calculation: aragonite
648                     if (i2_omarg(ji,jj) .eq. 0 .and. f_omarg(ji,jj) .lt. 1.0) then
649                        if (jk .eq. 1) then
650                           f2_ccd_arg(ji,jj) = fsdept(ji,jj,jk)
651                        else
652                           fq0 = f3_omarg(ji,jj,jk-1) - f_omarg(ji,jj)
653                           fq1 = f3_omarg(ji,jj,jk-1) - 1.0
654                           fq2 = fq1 / (fq0 + tiny(fq0))
655                           fq3 = fsdept(ji,jj,jk) - fsdept(ji,jj,jk-1)
656                           fq4 = fq2 * fq3
657                           f2_ccd_arg(ji,jj) = fsdept(ji,jj,jk-1) + fq4
658                        endif
659                        i2_omarg(ji,jj)   = 1
660                     endif
661                     if ( i2_omarg(ji,jj) .eq. 0 .and. jk .eq. mbathy(ji,jj) ) then
662                        !! reached seafloor and still no dissolution; set to seafloor (W-point)
663                        f2_ccd_arg(ji,jj) = fsdepw(ji,jj,jk+1)
664                        i2_omarg(ji,jj)   = 1
665                     endif
666                  endif
667               ENDDO
668            ENDDO
669         ENDDO
670      ENDIF
671# endif
672
673# if defined key_debug_medusa
674      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for full domain calculations'
675      CALL flush(numout)
676# endif 
677
678      !!----------------------------------------------------------------------
679      !! MEDUSA has unified equation through the water column
680      !! (Diff. from LOBSTER which has two sets: bio- and non-bio layers)
681      !! Statement below in LOBSTER is different: DO jk = 1, jpkbm1         
682      !!----------------------------------------------------------------------
683      !!
684      !! NOTE: the ordering of the loops below differs from that of some other
685      !! models; looping over the vertical dimension is the outermost loop and
686      !! this complicates some calculations (e.g. storage of vertical fluxes
687      !! that can otherwise be done via a singular variable require 2D fields
688      !! here); however, these issues are relatively easily resolved, but the
689      !! loops CANNOT be reordered without potentially causing code efficiency
690      !! problems (e.g. array indexing means that reordering the loops would
691      !! require skipping between widely-spaced memory location; potentially
692      !! outside those immediately cached)
693      !!
694      !! OPEN vertical loop
695      DO jk = 1,jpk
696         !! OPEN horizontal loops
697         DO jj = 2,jpjm1
698         DO ji = 2,jpim1
699            !! OPEN wet point IF..THEN loop
700            if (tmask(ji,jj,jk).eq.1) then               
701               !!======================================================================
702               !! SETUP LOCAL GRID CELL
703               !!======================================================================
704               !!
705               !!---------------------------------------------------------------------
706               !! Some notes on grid vertical structure
707               !! - fsdepw(ji,jj,jk) is the depth of the upper surface of level jk
708               !! - fsde3w(ji,jj,jk) is *approximately* the midpoint of level jk
709               !! - fse3t(ji,jj,jk)  is the thickness of level jk
710               !!---------------------------------------------------------------------
711               !!
712               !! AXY (01/03/10): set up level depth (bottom of level)
713               fdep1(ji,jj) = fsdepw(ji,jj,jk) + fse3t(ji,jj,jk)
714               !! AXY (28/11/16): local seafloor depth
715               !!                 previously mbathy(ji,jj) - 1, now mbathy(ji,jj)
716               mbathy(ji,jj) = mbathy(ji,jj)
717               !!
718               !! set up model tracers
719               !! negative values of state variables are not allowed to
720               !! contribute to the calculated fluxes
721               zchn(ji,jj) = max(0.,trn(ji,jj,jk,jpchn)) !! non-diatom chlorophyll
722               zchd(ji,jj) = max(0.,trn(ji,jj,jk,jpchd)) !! diatom chlorophyll
723               zphn(ji,jj) = max(0.,trn(ji,jj,jk,jpphn)) !! non-diatoms
724               zphd(ji,jj) = max(0.,trn(ji,jj,jk,jpphd)) !! diatoms
725               zpds(ji,jj) = max(0.,trn(ji,jj,jk,jppds)) !! diatom silicon
726               !! AXY (28/01/10): probably need to take account of chl/biomass connection
727               if (zchn(ji,jj).eq.0.) zphn(ji,jj) = 0.
728               if (zchd(ji,jj).eq.0.) zphd(ji,jj) = 0.
729               if (zphn(ji,jj).eq.0.) zchn(ji,jj) = 0.
730               if (zphd(ji,jj).eq.0.) zchd(ji,jj) = 0.
731          !! AXY (23/01/14): duh - why did I forget diatom silicon?
732          if (zpds(ji,jj).eq.0.) zphd(ji,jj) = 0.
733          if (zphd(ji,jj).eq.0.) zpds(ji,jj) = 0.
734               zzmi(ji,jj) = max(0.,trn(ji,jj,jk,jpzmi)) !! microzooplankton
735               zzme(ji,jj) = max(0.,trn(ji,jj,jk,jpzme)) !! mesozooplankton
736               zdet(ji,jj) = max(0.,trn(ji,jj,jk,jpdet)) !! detrital nitrogen
737               zdin(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) !! dissolved inorganic nitrogen
738               zsil(ji,jj) = max(0.,trn(ji,jj,jk,jpsil)) !! dissolved silicic acid
739               zfer(ji,jj) = max(0.,trn(ji,jj,jk,jpfer)) !! dissolved "iron"
740# if defined key_roam
741               zdtc(ji,jj) = max(0.,trn(ji,jj,jk,jpdtc)) !! detrital carbon
742               zdic(ji,jj) = max(0.,trn(ji,jj,jk,jpdic)) !! dissolved inorganic carbon
743               zalk(ji,jj) = max(0.,trn(ji,jj,jk,jpalk)) !! alkalinity
744               zoxy(ji,jj) = max(0.,trn(ji,jj,jk,jpoxy)) !! oxygen
745#  if defined key_axy_carbchem && defined key_mocsy
746               zpho(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) / 16.0 !! phosphate via DIN and Redfield
747#  endif
748               !!
749               !! also need physical parameters for gas exchange calculations
750               ztmp(ji,jj) = tsn(ji,jj,jk,jp_tem)
751               zsal(ji,jj) = tsn(ji,jj,jk,jp_sal)
752               !!
753          !! AXY (28/02/14): check input fields
754               if (ztmp(ji,jj) .lt. -3.0 .or. ztmp(ji,jj) .gt. 40.0 ) then
755                  IF(lwp) WRITE(numout,*) ' trc_bio_medusa: T WARNING 2D, ', &
756                  tsb(ji,jj,jk,jp_tem), tsn(ji,jj,jk,jp_tem), ' at (',    &
757                  ji, ',', jj, ',', jk, ') at time', kt
758        IF(lwp) WRITE(numout,*) ' trc_bio_medusa: T SWITCHING 2D, ', &
759                  tsn(ji,jj,jk,jp_tem), ' -> ', tsb(ji,jj,jk,jp_tem)
760                  ztmp(ji,jj) = tsb(ji,jj,jk,jp_tem) !! temperature
761               endif
762               if (zsal(ji,jj) .lt. 0.0 .or. zsal(ji,jj) .gt. 45.0 ) then
763                  IF(lwp) WRITE(numout,*) ' trc_bio_medusa: S WARNING 2D, ', &
764                  tsb(ji,jj,jk,jp_sal), tsn(ji,jj,jk,jp_sal), ' at (',    &
765                  ji, ',', jj, ',', jk, ') at time', kt
766               endif
767# else
768               zdtc(ji,jj) = zdet(ji,jj) * xthetad              !! implicit detrital carbon
769# endif
770# if defined key_debug_medusa
771               if (idf.eq.1) then
772               !! AXY (15/01/10)
773                  if (trn(ji,jj,jk,jpdin).lt.0.) then
774                     IF (lwp) write (numout,*) '------------------------------'
775                     IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR =', trn(ji,jj,jk,jpdin)
776                     IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR @', ji, jj, jk, kt
777                  endif
778                  if (trn(ji,jj,jk,jpsil).lt.0.) then
779                     IF (lwp) write (numout,*) '------------------------------'
780                     IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR =', trn(ji,jj,jk,jpsil)
781                     IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR @', ji, jj, jk, kt
782                  endif
783#  if defined key_roam
784                  if (trn(ji,jj,jk,jpdic).lt.0.) then
785                     IF (lwp) write (numout,*) '------------------------------'
786                     IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR =', trn(ji,jj,jk,jpdic)
787                     IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR @', ji, jj, jk, kt
788                  endif
789                  if (trn(ji,jj,jk,jpalk).lt.0.) then
790                     IF (lwp) write (numout,*) '------------------------------'
791                     IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR =', trn(ji,jj,jk,jpalk)
792                     IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR @', ji, jj, jk, kt
793                  endif
794                  if (trn(ji,jj,jk,jpoxy).lt.0.) then
795                     IF (lwp) write (numout,*) '------------------------------'
796                     IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR =', trn(ji,jj,jk,jpoxy)
797                     IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR @', ji, jj, jk, kt
798                  endif
799#  endif
800               endif
801# endif
802# if defined key_debug_medusa
803               !! report state variable values
804               if (idf.eq.1.AND.idfval.eq.1) then
805                  IF (lwp) write (numout,*) '------------------------------'
806                  IF (lwp) write (numout,*) 'fthk(',jk,') = ', fse3t(ji,jj,jk)
807                  IF (lwp) write (numout,*) 'zphn(',jk,') = ', zphn(ji,jj)
808                  IF (lwp) write (numout,*) 'zphd(',jk,') = ', zphd(ji,jj)
809                  IF (lwp) write (numout,*) 'zpds(',jk,') = ', zpds(ji,jj)
810                  IF (lwp) write (numout,*) 'zzmi(',jk,') = ', zzmi(ji,jj)
811                  IF (lwp) write (numout,*) 'zzme(',jk,') = ', zzme(ji,jj)
812                  IF (lwp) write (numout,*) 'zdet(',jk,') = ', zdet(ji,jj)
813                  IF (lwp) write (numout,*) 'zdin(',jk,') = ', zdin(ji,jj)
814                  IF (lwp) write (numout,*) 'zsil(',jk,') = ', zsil(ji,jj)
815                  IF (lwp) write (numout,*) 'zfer(',jk,') = ', zfer(ji,jj)
816#  if defined key_roam
817                  IF (lwp) write (numout,*) 'zdtc(',jk,') = ', zdtc(ji,jj)
818                  IF (lwp) write (numout,*) 'zdic(',jk,') = ', zdic(ji,jj)
819                  IF (lwp) write (numout,*) 'zalk(',jk,') = ', zalk(ji,jj)
820                  IF (lwp) write (numout,*) 'zoxy(',jk,') = ', zoxy(ji,jj)                 
821#  endif
822               endif
823# endif
824
825# if defined key_debug_medusa
826               if (idf.eq.1.AND.idfval.eq.1.AND.jk.eq.1) then
827                  IF (lwp) write (numout,*) '------------------------------'
828                  IF (lwp) write (numout,*) 'dust      = ', dust(ji,jj)
829               endif
830# endif
831
832               !! sum tracers for inventory checks
833               IF( lk_iomput ) THEN
834                  IF ( med_diag%INVTN%dgsave )   THEN
835                     ftot_n(ji,jj)  = ftot_n(ji,jj) + &
836                             (fse3t(ji,jj,jk) * ( zphn(ji,jj) + zphd(ji,jj) + zzmi(ji,jj) + zzme(ji,jj) + zdet(ji,jj) + zdin(ji,jj) ) )
837                  ENDIF
838                  IF ( med_diag%INVTSI%dgsave )  THEN
839                     ftot_si(ji,jj) = ftot_si(ji,jj) + & 
840                             (fse3t(ji,jj,jk) * ( zpds(ji,jj) + zsil(ji,jj) ) )
841                  ENDIF
842                  IF ( med_diag%INVTFE%dgsave )  THEN
843                     ftot_fe(ji,jj) = ftot_fe(ji,jj) + & 
844                             (fse3t(ji,jj,jk) * ( xrfn * ( zphn(ji,jj) + zphd(ji,jj) + zzmi(ji,jj) + zzme(ji,jj) + zdet(ji,jj) ) + zfer(ji,jj) ) )
845                  ENDIF
846# if defined key_roam
847                  IF ( med_diag%INVTC%dgsave )  THEN
848                     ftot_c(ji,jj)  = ftot_c(ji,jj) + & 
849                             (fse3t(ji,jj,jk) * ( (xthetapn * zphn(ji,jj)) + (xthetapd * zphd(ji,jj)) + &
850                             (xthetazmi * zzmi(ji,jj)) + (xthetazme * zzme(ji,jj)) + zdtc(ji,jj) +   &
851                             zdic(ji,jj) ) )
852                  ENDIF
853                  IF ( med_diag%INVTALK%dgsave ) THEN
854                     ftot_a(ji,jj)  = ftot_a(ji,jj) + (fse3t(ji,jj,jk) * ( zalk(ji,jj) ) )
855                  ENDIF
856                  IF ( med_diag%INVTO2%dgsave )  THEN
857                     ftot_o2(ji,jj) = ftot_o2(ji,jj) + (fse3t(ji,jj,jk) * ( zoxy(ji,jj) ) )
858                  ENDIF
859                  !!
860                  !! AXY (10/11/16): CMIP6 diagnostics
861                  IF ( med_diag%INTDISSIC%dgsave ) THEN
862                     intdissic(ji,jj) = intdissic(ji,jj) + (fse3t(ji,jj,jk) * zdic(ji,jj))
863                  ENDIF
864                  IF ( med_diag%INTDISSIN%dgsave ) THEN
865                     intdissin(ji,jj) = intdissin(ji,jj) + (fse3t(ji,jj,jk) * zdin(ji,jj))
866                  ENDIF
867                  IF ( med_diag%INTDISSISI%dgsave ) THEN
868                     intdissisi(ji,jj) = intdissisi(ji,jj) + (fse3t(ji,jj,jk) * zsil(ji,jj))
869                  ENDIF
870                  IF ( med_diag%INTTALK%dgsave ) THEN
871                     inttalk(ji,jj) = inttalk(ji,jj) + (fse3t(ji,jj,jk) * zalk(ji,jj))
872                  ENDIF
873                  IF ( med_diag%O2min%dgsave ) THEN
874                     if ( zoxy(ji,jj) < o2min(ji,jj) ) then
875                        o2min(ji,jj)  = zoxy(ji,jj)
876                        IF ( med_diag%ZO2min%dgsave ) THEN
877                           zo2min(ji,jj) = (fsdepw(ji,jj,jk) + fdep1(ji,jj)) / 2. !! layer midpoint
878                        ENDIF
879                     endif
880                  ENDIF
881# endif
882               ENDIF
883
884               CALL flush(numout)
885
886               !!======================================================================
887               !! LOCAL GRID CELL CALCULATIONS
888               !!======================================================================
889               !!
890# if defined key_roam
891               if ( jk .eq. 1 ) then
892                  !!----------------------------------------------------------------------
893                  !! Air-sea gas exchange
894                  !!----------------------------------------------------------------------
895                  IF (lk_oasis) THEN
896                     f_xco2a = PCO2a_in_cpl(ji,jj)        !! use 2D atm xCO2 from atm coupling
897                  ENDIF
898                  !!
899                  !! AXY (23/06/15): as part of an effort to update the carbonate chemistry
900                  !!                 in MEDUSA, the gas transfer velocity used in the carbon
901                  !!                 and oxygen cycles has been harmonised and is calculated
902                  !!                 by the same function here; this harmonisation includes
903                  !!                 changes to the PML carbonate chemistry scheme so that
904                  !!                 it too makes use of the same gas transfer velocity; the
905                  !!                 preferred parameterisation of this is Wanninkhof (2014),
906                  !!                 option 7
907                  !!
908#   if defined key_debug_medusa
909                     IF (lwp) write (numout,*) 'trc_bio_medusa: entering gas_transfer'
910                     CALL flush(numout)
911#   endif
912                  CALL gas_transfer( wndm(ji,jj), 1, 7, &  ! inputs
913                                     f_kw660(ji,jj) )        ! outputs
914#   if defined key_debug_medusa
915                     IF (lwp) write (numout,*) 'trc_bio_medusa: exiting gas_transfer'
916                     CALL flush(numout)
917#   endif
918                  !!
919                  !! air pressure (atm); ultimately this will use air pressure at the base
920                  !! of the UKESM1 atmosphere
921                  !!                                     
922                  f_pp0(ji,jj)   = 1.0
923                  !!
924                  !! IF(lwp) WRITE(numout,*) ' MEDUSA ztmp    =', ztmp(ji,jj)
925                  !! IF(lwp) WRITE(numout,*) ' MEDUSA zwind_i =', zwind_i(ji,jj)
926                  !! IF(lwp) WRITE(numout,*) ' MEDUSA zwind_j =', zwind_j(ji,jj)
927                  !! IF(lwp) WRITE(numout,*) ' MEDUSA wndm    =', wndm(ji,jj)
928                  !! IF(lwp) WRITE(numout,*) ' MEDUSA fr_i    =', fr_i(ji,jj)
929                  !!
930#  if defined key_axy_carbchem
931#   if defined key_mocsy
932                  !!
933                  !! AXY (22/06/15): use Orr & Epitalon (2015) MOCSY-2 carbonate
934                  !!                 chemistry package; note that depth is set to
935                  !!                 zero in this call
936                  CALL mocsy_interface( ztmp(ji,jj), zsal(ji,jj), zalk(ji,jj), zdic(ji,jj), zsil(ji,jj), zpho(ji,jj),        &  ! inputs
937                  f_pp0(ji,jj), 0.0, gphit(ji,jj), f_kw660(ji,jj), f_xco2a, 1,                   &  ! inputs
938                  f_ph(ji,jj), f_pco2w(ji,jj), f_fco2w(ji,jj), f_h2co3(ji,jj), f_hco3(ji,jj), f_co3(ji,jj), f_omarg(ji,jj),  &  ! outputs
939                  f_omcal(ji,jj), f_BetaD(ji,jj), f_rhosw(ji,jj), f_opres(ji,jj), f_insitut(ji,jj),            &  ! outputs
940                  f_pco2atm(ji,jj), f_fco2atm(ji,jj), f_schmidtco2(ji,jj), f_kwco2(ji,jj), f_K0(ji,jj),               &  ! outputs
941                  f_co2starair(ji,jj), f_co2flux(ji,jj), f_dpco2(ji,jj) )                                  ! outputs
942                  !!
943                  f_TDIC(ji,jj) = (zdic(ji,jj) / f_rhosw(ji,jj)) * 1000. ! mmol / m3 -> umol / kg
944                  f_TALK(ji,jj) = (zalk(ji,jj) / f_rhosw(ji,jj)) * 1000. !  meq / m3 ->  ueq / kg
945                  f_dcf(ji,jj)  = f_rhosw(ji,jj)
946#   else                 
947                  iters(ji,jj) = 0
948                  !!
949                  !! carbon dioxide (CO2); Jerry Blackford code (ostensibly OCMIP-2, but not)
950                  CALL trc_co2_medusa( ztmp(ji,jj), zsal(ji,jj), zdic(ji,jj), zalk(ji,jj), 0.0, f_kw660(ji,jj), f_xco2a,  &  ! inputs
951                  f_ph(ji,jj), f_pco2w(ji,jj), f_h2co3(ji,jj), f_hco3(ji,jj), f_co3(ji,jj), f_omcal(ji,jj),               &  ! outputs
952                  f_omarg(ji,jj), f_co2flux(ji,jj), f_TDIC(ji,jj), f_TALK(ji,jj), f_dcf(ji,jj), f_henry(ji,jj), iters(ji,jj) )      ! outputs
953                  !!
954                  !! AXY (09/01/14): removed iteration and NaN checks; these have
955                  !!                 been moved to trc_co2_medusa together with a
956                  !!                 fudge that amends erroneous values (this is
957                  !!                 intended to be a temporary fudge!); the
958                  !!                 output warnings are retained here so that
959                  !!                 failure position can be determined
960                  if (iters(ji,jj) .eq. 25) then
961                     IF(lwp) WRITE(numout,*) ' trc_bio_medusa: ITERS WARNING, ', &
962                     iters(ji,jj), ' AT (', ji, ', ', jj, ', ', jk, ') AT ', kt
963                  endif
964#   endif
965#  else
966                  !! AXY (18/04/13): switch off carbonate chemistry calculations; provide
967                  !!                 quasi-sensible alternatives
968                  f_ph(ji,jj)           = 8.1
969                  f_pco2w(ji,jj)        = f_xco2a
970                  f_h2co3(ji,jj)        = 0.005 * zdic(ji,jj)
971                  f_hco3(ji,jj)         = 0.865 * zdic(ji,jj)
972                  f_co3(ji,jj)          = 0.130 * zdic(ji,jj)
973                  f_omcal(ji,jj) = 4.
974                  f_omarg(ji,jj) = 2.
975                  f_co2flux(ji,jj)      = 0.
976                  f_TDIC(ji,jj)         = zdic(ji,jj)
977                  f_TALK(ji,jj)         = zalk(ji,jj)
978                  f_dcf(ji,jj)          = 1.026
979                  f_henry(ji,jj)        = 1.
980                  !! AXY (23/06/15): add in some extra MOCSY diagnostics
981                  f_fco2w(ji,jj)        = f_xco2a
982                  f_BetaD(ji,jj)        = 1.
983                  f_rhosw(ji,jj)        = 1.026
984                  f_opres(ji,jj)        = 0.
985                  f_insitut(ji,jj)      = ztmp(ji,jj)
986                  f_pco2atm(ji,jj)      = f_xco2a
987                  f_fco2atm(ji,jj)      = f_xco2a
988                  f_schmidtco2(ji,jj)   = 660.
989                  f_kwco2(ji,jj)        = 0.
990                  f_K0(ji,jj)           = 0.
991                  f_co2starair(ji,jj)   = f_xco2a
992                  f_dpco2(ji,jj)        = 0.
993#  endif
994                  !!
995                  !! mmol/m2/s -> mmol/m3/d; correct for sea-ice; divide through by layer thickness
996                  f_co2flux(ji,jj) = (1. - fr_i(ji,jj)) * f_co2flux(ji,jj) * 86400. / fse3t(ji,jj,jk)
997                  !!
998                  !! oxygen (O2); OCMIP-2 code
999                  !! AXY (23/06/15): amend input list for oxygen to account for common gas
1000                  !!                 transfer velocity
1001                  !! Note that f_kwo2 is an about from the subroutine below,
1002                  !! which doesn't seem to be used - marc 10/4/17
1003                  CALL trc_oxy_medusa( ztmp(ji,jj), zsal(ji,jj), f_kw660(ji,jj), f_pp0(ji,jj), zoxy(ji,jj),  &  ! inputs
1004                  f_kwo2(ji,jj), f_o2flux(ji,jj), f_o2sat(ji,jj) )                                ! outputs
1005                  !!
1006                  !! mmol/m2/s -> mol/m3/d; correct for sea-ice; divide through by layer thickness
1007                  f_o2flux(ji,jj)  = (1. - fr_i(ji,jj)) * f_o2flux(ji,jj) * 86400. / fse3t(ji,jj,jk)
1008                  !!
1009                  !! Jpalm (08-2014)
1010                  !! DMS surface concentration calculation
1011                  !! initialy added for UKESM1 model.
1012                  !! using MET-OFFICE subroutine.
1013                  !! DMS module only needs Chl concentration and MLD
1014                  !! to get an aproximate value of DMS concentration.
1015                  !! air-sea fluxes are calculated by atmospheric chemitry model
1016                  !! from atm and oc-surface concentrations.
1017                  !!
1018                  !! AXY (13/03/15): this is amended to calculate all of the DMS
1019                  !!                 estimates examined during UKESM1 (see comments
1020                  !!                 in trcdms_medusa.F90)
1021                  !!
1022                  IF (jdms .eq. 1) THEN
1023                     !!
1024                     !! feed in correct inputs
1025                     if (jdms_input .eq. 0) then
1026                        !! use instantaneous inputs
1027                        CALL trc_dms_medusa( zchn(ji,jj), zchd(ji,jj), hmld(ji,jj), qsr(ji,jj), zdin(ji,jj), &  ! inputs
1028                        dms_andr(ji,jj), dms_simo(ji,jj), dms_aran(ji,jj), dms_hall(ji,jj) )                           ! outputs
1029                     else
1030                        !! use diel-average inputs
1031                        CALL trc_dms_medusa( zn_dms_chn(ji,jj), zn_dms_chd(ji,jj), &  ! inputs
1032                        zn_dms_mld(ji,jj), zn_dms_qsr(ji,jj), zn_dms_din(ji,jj),   &  ! inputs
1033                        dms_andr(ji,jj), dms_simo(ji,jj), dms_aran(ji,jj), dms_hall(ji,jj) )                      ! outputs
1034                     endif
1035                     !!
1036                     !! assign correct output to variable passed to atmosphere
1037                     if     (jdms_model .eq. 1) then
1038                        dms_surf(ji,jj) = dms_andr(ji,jj)
1039                     elseif (jdms_model .eq. 2) then
1040                        dms_surf(ji,jj) = dms_simo(ji,jj)
1041                     elseif (jdms_model .eq. 3) then
1042                        dms_surf(ji,jj) = dms_aran(ji,jj)
1043                     elseif (jdms_model .eq. 4) then
1044                        dms_surf(ji,jj) = dms_hall(ji,jj)
1045                     endif
1046                     !!
1047                     !! 2D diag through iom_use
1048                     IF( lk_iomput ) THEN
1049                       IF( med_diag%DMS_SURF%dgsave ) THEN
1050                         dms_surf2d(ji,jj) = dms_surf(ji,jj)
1051                       ENDIF
1052                       IF( med_diag%DMS_ANDR%dgsave ) THEN
1053                         dms_andr2d(ji,jj) = dms_andr(ji,jj)
1054                       ENDIF
1055                       IF( med_diag%DMS_SIMO%dgsave ) THEN
1056                         dms_simo2d(ji,jj) = dms_simo(ji,jj)
1057                       ENDIF
1058                       IF( med_diag%DMS_ARAN%dgsave ) THEN
1059                         dms_aran2d(ji,jj) = dms_aran(ji,jj)
1060                       ENDIF
1061                       IF( med_diag%DMS_HALL%dgsave ) THEN
1062                         dms_hall2d(ji,jj) = dms_hall(ji,jj)
1063                       ENDIF
1064#   if defined key_debug_medusa
1065                       IF (lwp) write (numout,*) 'trc_bio_medusa: finish calculating dms'
1066                     CALL flush(numout)
1067#   endif
1068                     ENDIF
1069                     !! End iom
1070                  ENDIF
1071                  !! End DMS Loop
1072                  !!
1073                  !! store 2D outputs
1074                  !!
1075                  !! JPALM -- 17-11-16 -- put fgco2 out of diag request
1076                  !!                    is needed for coupling; pass through restart
1077                  !! IF( med_diag%FGCO2%dgsave ) THEN
1078                     !! convert from  mol/m2/day to kg/m2/s
1079                     fgco2(ji,jj) = f_co2flux(ji,jj) * fse3t(ji,jj,jk) * CO2flux_conv  !! mmol-C/m3/d -> kg-CO2/m2/s
1080                  !! ENDIF
1081                  IF ( lk_iomput ) THEN
1082                      IF( med_diag%ATM_PCO2%dgsave ) THEN
1083                         f_pco2a2d(ji,jj) = f_pco2atm(ji,jj)
1084                      ENDIF
1085                      IF( med_diag%OCN_PCO2%dgsave ) THEN
1086                         f_pco2w2d(ji,jj) = f_pco2w(ji,jj)
1087                      ENDIF
1088                      IF( med_diag%CO2FLUX%dgsave ) THEN
1089                         f_co2flux2d(ji,jj) = f_co2flux(ji,jj) * fse3t(ji,jj,jk)           !! mmol/m3/d -> mmol/m2/d
1090                      ENDIF
1091                      IF( med_diag%TCO2%dgsave ) THEN
1092                         f_TDIC2d(ji,jj) = f_TDIC(ji,jj)
1093                      ENDIF
1094                      IF( med_diag%TALK%dgsave ) THEN
1095                         f_TALK2d(ji,jj) = f_TALK(ji,jj)
1096                      ENDIF
1097                      IF( med_diag%KW660%dgsave ) THEN
1098                         f_kw6602d(ji,jj) = f_kw660(ji,jj)
1099                      ENDIF
1100                      IF( med_diag%ATM_PP0%dgsave ) THEN
1101                         f_pp02d(ji,jj) = f_pp0(ji,jj)
1102                      ENDIF
1103                      IF( med_diag%O2FLUX%dgsave ) THEN
1104                         f_o2flux2d(ji,jj) = f_o2flux(ji,jj)
1105                      ENDIF
1106                      IF( med_diag%O2SAT%dgsave ) THEN
1107                         f_o2sat2d(ji,jj) = f_o2sat(ji,jj)
1108                      ENDIF
1109                      !! AXY (24/11/16): add in extra MOCSY diagnostics
1110                      IF( med_diag%ATM_XCO2%dgsave ) THEN
1111                         f_xco2a_2d(ji,jj) = f_xco2a
1112                      ENDIF
1113                      IF( med_diag%OCN_FCO2%dgsave ) THEN
1114                         f_fco2w_2d(ji,jj) = f_fco2w(ji,jj)
1115                      ENDIF
1116                      IF( med_diag%ATM_FCO2%dgsave ) THEN
1117                         f_fco2a_2d(ji,jj) = f_fco2atm(ji,jj)
1118                      ENDIF
1119                      IF( med_diag%OCN_RHOSW%dgsave ) THEN
1120                         f_ocnrhosw_2d(ji,jj) = f_rhosw(ji,jj)
1121                      ENDIF
1122                      IF( med_diag%OCN_SCHCO2%dgsave ) THEN
1123                         f_ocnschco2_2d(ji,jj) = f_schmidtco2(ji,jj)
1124                      ENDIF
1125                      IF( med_diag%OCN_KWCO2%dgsave ) THEN
1126                         f_ocnkwco2_2d(ji,jj) = f_kwco2(ji,jj)
1127                      ENDIF
1128                      IF( med_diag%OCN_K0%dgsave ) THEN
1129                         f_ocnk0_2d(ji,jj) = f_K0(ji,jj)
1130                      ENDIF
1131                      IF( med_diag%CO2STARAIR%dgsave ) THEN
1132                         f_co2starair_2d(ji,jj) = f_co2starair(ji,jj)
1133                      ENDIF
1134                      IF( med_diag%OCN_DPCO2%dgsave ) THEN
1135                         f_ocndpco2_2d(ji,jj) = f_dpco2(ji,jj)
1136                      ENDIF
1137                  ENDIF
1138                  !!
1139               endif
1140               !! End jk = 1 loop within ROAM key
1141
1142               !! AXY (11/11/16): CMIP6 oxygen saturation 3D diagnostic
1143               IF ( med_diag%O2SAT3%dgsave ) THEN
1144                  call oxy_sato( ztmp(ji,jj), zsal(ji,jj), f_o2sat3 )
1145                  o2sat3(ji, jj, jk) = f_o2sat3
1146               ENDIF
1147
1148# endif
1149
1150               if ( jk .eq. 1 ) then
1151                  !!----------------------------------------------------------------------
1152                  !! River inputs
1153                  !!----------------------------------------------------------------------
1154                  !!
1155                  !! runoff comes in as        kg / m2 / s
1156                  !! used and written out as   m3 / m2 / d (= m / d)
1157                  !! where                     1000 kg / m2 / d = 1 m3 / m2 / d = 1 m / d
1158                  !!
1159                  !! AXY (17/07/14): the compiler doesn't like this line for some reason;
1160                  !!                 as MEDUSA doesn't even use runoff for riverine inputs,
1161                  !!                 a temporary solution is to switch off runoff entirely
1162                  !!                 here; again, this change is one of several that will
1163                  !!                 need revisiting once MEDUSA has bedded down in UKESM1;
1164                  !!                 particularly so if the land scheme provides information
1165                  !!                 concerning nutrient fluxes
1166                  !!
1167                  !! f_runoff(ji,jj) = sf_rnf(1)%fnow(ji,jj,1) / 1000. * 60. * 60. * 24.
1168                  f_runoff(ji,jj) = 0.0
1169                  !!
1170                  !! nutrients are added via rivers to the model in one of two ways:
1171                  !!   1. via river concentration; i.e. the average nutrient concentration
1172                  !!      of a river water is described by a spatial file, and this is
1173                  !!      multiplied by runoff to give a nutrient flux
1174                  !!   2. via direct river flux; i.e. the average nutrient flux due to
1175                  !!      rivers is described by a spatial file, and this is simply applied
1176                  !!      as a direct nutrient flux (i.e. it does not relate or respond to
1177                  !!      model runoff)
1178                  !! nutrient fields are derived from the GlobalNEWS 2 database; carbon and
1179                  !! alkalinity are derived from continent-scale DIC estimates (Huang et al.,
1180                  !! 2012) and some Arctic river alkalinity estimates (Katya?)
1181                  !!
1182                  !! as of 19/07/12, riverine nutrients can now be spread vertically across
1183                  !! several grid cells rather than just poured into the surface box; this
1184                  !! block of code is still executed, however, to set up the total amounts
1185                  !! of nutrient entering via rivers
1186                  !!
1187                  !! nitrogen
1188                  if (jriver_n .eq. 1) then
1189                     !! river concentration specified; use runoff to calculate input
1190                     f_riv_n(ji,jj) = f_runoff(ji,jj) * riv_n(ji,jj)
1191                  elseif (jriver_n .eq. 2) then
1192                     !! river flux specified; independent of runoff
1193                     f_riv_n(ji,jj) = riv_n(ji,jj)
1194                  endif
1195                  !!
1196                  !! silicon
1197                  if (jriver_si .eq. 1) then
1198                     !! river concentration specified; use runoff to calculate input
1199                     f_riv_si(ji,jj) = f_runoff(ji,jj) * riv_si(ji,jj)
1200                  elseif (jriver_si .eq. 2) then
1201                     !! river flux specified; independent of runoff
1202                     f_riv_si(ji,jj) = riv_si(ji,jj)
1203                  endif
1204                  !!
1205                  !! carbon
1206                  if (jriver_c .eq. 1) then
1207                     !! river concentration specified; use runoff to calculate input
1208                     f_riv_c(ji,jj) = f_runoff(ji,jj) * riv_c(ji,jj)
1209                  elseif (jriver_c .eq. 2) then
1210                     !! river flux specified; independent of runoff
1211                     f_riv_c(ji,jj) = riv_c(ji,jj)
1212                  endif
1213                  !!
1214                  !! alkalinity
1215                  if (jriver_alk .eq. 1) then
1216                     !! river concentration specified; use runoff to calculate input
1217                     f_riv_alk(ji,jj) = f_runoff(ji,jj) * riv_alk(ji,jj)
1218                  elseif (jriver_alk .eq. 2) then
1219                     !! river flux specified; independent of runoff
1220                     f_riv_alk(ji,jj) = riv_alk(ji,jj)
1221                  endif
1222
1223               endif
1224
1225               !!----------------------------------------------------------------------
1226               !! Chlorophyll calculations
1227               !!----------------------------------------------------------------------
1228               !!
1229               !! non-diatoms
1230          if (zphn(ji,jj).GT.rsmall) then
1231                  fthetan(ji,jj) = max(tiny(zchn(ji,jj)), (zchn(ji,jj) * xxi) / (zphn(ji,jj) + tiny(zphn(ji,jj))))
1232                  faln(ji,jj)    = xaln * fthetan(ji,jj)
1233               else
1234                  fthetan(ji,jj) = 0.
1235                  faln(ji,jj)    = 0.
1236               endif
1237               !!
1238               !! diatoms
1239          if (zphd(ji,jj).GT.rsmall) then
1240                  fthetad(ji,jj) = max(tiny(zchd(ji,jj)), (zchd(ji,jj) * xxi) / (zphd(ji,jj) + tiny(zphd(ji,jj))))
1241                  fald(ji,jj)    = xald * fthetad(ji,jj)
1242               else
1243                  fthetad(ji,jj) = 0.
1244                  fald(ji,jj)    = 0.
1245               endif
1246
1247# if defined key_debug_medusa
1248               !! report biological calculations
1249               if (idf.eq.1.AND.idfval.eq.1) then
1250                  IF (lwp) write (numout,*) '------------------------------'
1251                  IF (lwp) write (numout,*) 'faln(',jk,') = ', faln(ji,jj)
1252                  IF (lwp) write (numout,*) 'fald(',jk,') = ', fald(ji,jj)
1253               endif
1254# endif
1255
1256               !!----------------------------------------------------------------------
1257               !! Phytoplankton light limitation
1258               !!----------------------------------------------------------------------
1259               !!
1260               !! It is assumed xpar is the depth-averaged (vertical layer) PAR
1261               !! Light limitation (check self-shading) in W/m2
1262               !!
1263               !! Note that there is no temperature dependence in phytoplankton
1264               !! growth rate or any other function.
1265               !! In calculation of Chl/Phy ratio tiny(phyto) is introduced to avoid
1266               !! NaNs in case of Phy==0. 
1267               !!
1268               !! fthetad and fthetan are Chl:C ratio (gChl/gC) in diat and non-diat:
1269               !! for 1:1 Chl:P ratio (mgChl/mmolN) theta=0.012
1270               !!
1271               !! AXY (16/07/09)
1272               !! temperature for new Eppley style phytoplankton growth
1273               fun_T(ji,jj)   = 1.066**(1.0 * tsn(ji,jj,jk,jp_tem))
1274               !! AXY (16/05/11): add in new Q10 (1.5, not 2.0) for
1275               !phytoplankton
1276               !!                 growth; remin. unaffected
1277               fun_Q10(ji,jj) = jq10**((tsn(ji,jj,jk,jp_tem) - 0.0) / 10.0)
1278               if (jphy.eq.1) then
1279                  xvpnT(ji,jj) = xvpn * fun_T(ji,jj)
1280                  xvpdT(ji,jj) = xvpd * fun_T(ji,jj)
1281               elseif (jphy.eq.2) then
1282                  xvpnT(ji,jj) = xvpn * fun_Q10(ji,jj)
1283                  xvpdT(ji,jj) = xvpd * fun_Q10(ji,jj)
1284               else
1285                  xvpnT(ji,jj) = xvpn
1286                  xvpdT(ji,jj) = xvpd
1287               endif
1288               !!
1289               !! non-diatoms
1290               fchn1(ji,jj)   = (xvpnT(ji,jj) * xvpnT(ji,jj)) + (faln(ji,jj) * faln(ji,jj) * xpar(ji,jj,jk) * xpar(ji,jj,jk))
1291               if (fchn1(ji,jj).GT.rsmall) then
1292                  fchn(ji,jj)    = xvpnT(ji,jj) / (sqrt(fchn1(ji,jj)) + tiny(fchn1(ji,jj)))
1293               else
1294                  fchn(ji,jj)    = 0.
1295               endif
1296               fjln(ji,jj)    = fchn(ji,jj) * faln(ji,jj) * xpar(ji,jj,jk) !! non-diatom J term
1297               fjlim_pn(ji,jj) = fjln(ji,jj) / xvpnT(ji,jj)
1298               !!
1299               !! diatoms
1300               fchd1(ji,jj)   = (xvpdT(ji,jj) * xvpdT(ji,jj)) + (fald(ji,jj) * fald(ji,jj) * xpar(ji,jj,jk) * xpar(ji,jj,jk))
1301               if (fchd1(ji,jj).GT.rsmall) then
1302                  fchd(ji,jj)    = xvpdT(ji,jj) / (sqrt(fchd1(ji,jj)) + tiny(fchd1(ji,jj)))
1303               else
1304                  fchd(ji,jj)    = 0.
1305               endif
1306               fjld(ji,jj)    = fchd(ji,jj) * fald(ji,jj) * xpar(ji,jj,jk) !! diatom J term
1307               fjlim_pd(ji,jj) = fjld(ji,jj) / xvpdT(ji,jj)
1308     
1309# if defined key_debug_medusa
1310               !! report phytoplankton light limitation
1311               if (idf.eq.1.AND.idfval.eq.1) then
1312                  IF (lwp) write (numout,*) '------------------------------'
1313                  IF (lwp) write (numout,*) 'fchn(',jk,') = ', fchn(ji,jj)
1314                  IF (lwp) write (numout,*) 'fchd(',jk,') = ', fchd(ji,jj)
1315                  IF (lwp) write (numout,*) 'fjln(',jk,') = ', fjln(ji,jj)
1316                  IF (lwp) write (numout,*) 'fjld(',jk,') = ', fjld(ji,jj)
1317               endif
1318# endif
1319
1320               !!----------------------------------------------------------------------
1321               !! Phytoplankton nutrient limitation
1322               !!----------------------------------------------------------------------
1323               !!
1324               !! non-diatoms (N, Fe)
1325               fnln(ji,jj) = zdin(ji,jj) / (zdin(ji,jj) + xnln) !! non-diatom Qn term
1326               ffln(ji,jj) = zfer(ji,jj) / (zfer(ji,jj) + xfln) !! non-diatom Qf term
1327               !!
1328               !! diatoms (N, Si, Fe)
1329               fnld(ji,jj) = zdin(ji,jj) / (zdin(ji,jj) + xnld) !! diatom Qn term
1330               fsld(ji,jj) = zsil(ji,jj) / (zsil(ji,jj) + xsld) !! diatom Qs term
1331               ffld(ji,jj) = zfer(ji,jj) / (zfer(ji,jj) + xfld) !! diatom Qf term
1332
1333# if defined key_debug_medusa
1334               !! report phytoplankton nutrient limitation
1335               if (idf.eq.1.AND.idfval.eq.1) then
1336                  IF (lwp) write (numout,*) '------------------------------'
1337                  IF (lwp) write (numout,*) 'fnln(',jk,') = ', fnln(ji,jj)
1338                  IF (lwp) write (numout,*) 'fnld(',jk,') = ', fnld(ji,jj)
1339                  IF (lwp) write (numout,*) 'ffln(',jk,') = ', ffln(ji,jj)
1340                  IF (lwp) write (numout,*) 'ffld(',jk,') = ', ffld(ji,jj)
1341                  IF (lwp) write (numout,*) 'fsld(',jk,') = ', fsld(ji,jj)
1342               endif
1343# endif
1344
1345               !!----------------------------------------------------------------------
1346               !! Primary production (non-diatoms)
1347               !! (note: still needs multiplying by phytoplankton concentration)
1348               !!----------------------------------------------------------------------
1349               !!
1350               if (jliebig .eq. 0) then
1351                  !! multiplicative nutrient limitation
1352                  fpnlim(ji,jj) = fnln(ji,jj) * ffln(ji,jj)
1353               elseif (jliebig .eq. 1) then
1354                  !! Liebig Law (= most limiting) nutrient limitation
1355                  fpnlim(ji,jj) = min(fnln(ji,jj), ffln(ji,jj))
1356               endif
1357               fprn(ji,jj) = fjln(ji,jj) * fpnlim(ji,jj)
1358
1359               !!----------------------------------------------------------------------
1360               !! Primary production (diatoms)
1361               !! (note: still needs multiplying by phytoplankton concentration)
1362               !!
1363               !! production here is split between nitrogen production and that of
1364               !! silicon; depending upon the "intracellular" ratio of Si:N, model
1365               !! diatoms will uptake nitrogen/silicon differentially; this borrows
1366               !! from the diatom model of Mongin et al. (2006)
1367               !!----------------------------------------------------------------------
1368               !!
1369               if (jliebig .eq. 0) then
1370                  !! multiplicative nutrient limitation
1371                  fpdlim(ji,jj) = fnld(ji,jj) * ffld(ji,jj)
1372               elseif (jliebig .eq. 1) then
1373                  !! Liebig Law (= most limiting) nutrient limitation
1374                  fpdlim(ji,jj) = min(fnld(ji,jj), ffld(ji,jj))
1375               endif
1376               !!
1377          if (zphd(ji,jj).GT.rsmall .AND. zpds(ji,jj).GT.rsmall) then
1378                  !! "intracellular" elemental ratios
1379                  ! fsin(ji,jj)  = zpds(ji,jj) / (zphd(ji,jj) + tiny(zphd(ji,jj)))
1380                  ! fnsi(ji,jj)  = zphd(ji,jj) / (zpds(ji,jj) + tiny(zpds(ji,jj)))
1381                  fsin(ji,jj) = 0.0
1382                  IF( zphd(ji,jj) .GT. rsmall) fsin(ji,jj)  = zpds(ji,jj) / zphd(ji,jj)
1383                  fnsi(ji,jj) = 0.0
1384                  IF( zpds(ji,jj) .GT. rsmall) fnsi(ji,jj)  = zphd(ji,jj) / zpds(ji,jj)
1385                  !! AXY (23/02/10): these next variables derive from Mongin et al. (2003)
1386                  fsin1 = 3.0 * xsin0 !! = 0.6
1387                  fnsi1 = 1.0 / fsin1 !! = 1.667
1388                  fnsi2 = 1.0 / xsin0 !! = 5.0
1389                  !!
1390                  !! conditionalities based on ratios
1391                  !! nitrogen (and iron and carbon)
1392                  if (fsin(ji,jj).le.xsin0) then
1393                     fprd(ji,jj)  = 0.0
1394                     fsld2(ji,jj) = 0.0
1395                  elseif (fsin(ji,jj).lt.fsin1) then
1396                     fprd(ji,jj)  = xuif * ((fsin(ji,jj) - xsin0) / (fsin(ji,jj) + tiny(fsin(ji,jj)))) * (fjld(ji,jj) * fpdlim(ji,jj))
1397                     fsld2(ji,jj) = xuif * ((fsin(ji,jj) - xsin0) / (fsin(ji,jj) + tiny(fsin(ji,jj))))
1398                  elseif (fsin(ji,jj).ge.fsin1) then
1399                     fprd(ji,jj)  = (fjld(ji,jj) * fpdlim(ji,jj))
1400                     fsld2(ji,jj) = 1.0
1401                  endif
1402                  !!
1403                  !! silicon
1404                  if (fsin(ji,jj).lt.fnsi1) then
1405                     fprds(ji,jj) = (fjld(ji,jj) * fsld(ji,jj))
1406                  elseif (fsin(ji,jj).lt.fnsi2) then
1407                     fprds(ji,jj) = xuif * ((fnsi(ji,jj) - xnsi0) / (fnsi(ji,jj) + tiny(fnsi(ji,jj)))) * (fjld(ji,jj) * fsld(ji,jj))
1408                  else
1409                     fprds(ji,jj) = 0.0
1410                  endif     
1411               else
1412                  fsin(ji,jj)  = 0.0
1413                  fnsi(ji,jj)  = 0.0
1414                  fprd(ji,jj)  = 0.0
1415                  fsld2(ji,jj) = 0.0
1416                  fprds(ji,jj) = 0.0
1417               endif
1418
1419# if defined key_debug_medusa
1420               !! report phytoplankton growth (including diatom silicon submodel)
1421               if (idf.eq.1.AND.idfval.eq.1) then
1422                  IF (lwp) write (numout,*) '------------------------------'
1423                  IF (lwp) write (numout,*) 'fsin(',jk,')   = ', fsin(ji,jj)
1424                  IF (lwp) write (numout,*) 'fnsi(',jk,')   = ', fnsi(ji,jj)
1425                  IF (lwp) write (numout,*) 'fsld2(',jk,')  = ', fsld2(ji,jj)
1426                  IF (lwp) write (numout,*) 'fprn(',jk,')   = ', fprn(ji,jj)
1427                  IF (lwp) write (numout,*) 'fprd(',jk,')   = ', fprd(ji,jj)
1428                  IF (lwp) write (numout,*) 'fprds(',jk,')  = ', fprds(ji,jj)
1429               endif
1430# endif
1431
1432               !!----------------------------------------------------------------------
1433               !! Mixed layer primary production
1434               !! this block calculates the amount of primary production that occurs
1435               !! within the upper mixed layer; this allows the separate diagnosis
1436               !! of "sub-surface" primary production; it does assume that short-
1437               !! term variability in mixed layer depth doesn't mess with things
1438               !! though
1439               !!----------------------------------------------------------------------
1440               !!
1441               if (fdep1(ji,jj).le.hmld(ji,jj)) then
1442                  !! this level is entirely in the mixed layer
1443                  fq0 = 1.0
1444               elseif (fsdepw(ji,jj,jk).ge.hmld(ji,jj)) then
1445                  !! this level is entirely below the mixed layer
1446                  fq0 = 0.0
1447               else
1448                  !! this level straddles the mixed layer
1449                  fq0 = (hmld(ji,jj) - fsdepw(ji,jj,jk)) / fse3t(ji,jj,jk)
1450               endif
1451               !!
1452               fprn_ml(ji,jj) = fprn_ml(ji,jj) + (fprn(ji,jj) * zphn(ji,jj) * fse3t(ji,jj,jk) * fq0)
1453               fprd_ml(ji,jj) = fprd_ml(ji,jj) + (fprd(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk) * fq0)
1454               
1455               !!----------------------------------------------------------------------
1456               !! Vertical Integral --
1457               !!----------------------------------------------------------------------
1458               ftot_pn(ji,jj)  = ftot_pn(ji,jj)  + (zphn(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral non-diatom phytoplankton
1459               ftot_pd(ji,jj)  = ftot_pd(ji,jj)  + (zphd(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral diatom phytoplankton
1460               ftot_zmi(ji,jj) = ftot_zmi(ji,jj) + (zzmi(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral microzooplankton
1461               ftot_zme(ji,jj) = ftot_zme(ji,jj) + (zzme(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral mesozooplankton
1462               ftot_det(ji,jj) = ftot_det(ji,jj) + (zdet(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral slow detritus, nitrogen
1463               ftot_dtc(ji,jj) = ftot_dtc(ji,jj) + (zdtc(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral slow detritus, carbon
1464               
1465               !!----------------------------------------------------------------------
1466               !! More chlorophyll calculations
1467               !!----------------------------------------------------------------------
1468               !!
1469               !! frn(ji,jj) = (xthetam / fthetan(ji,jj)) * (fprn(ji,jj) / (fthetan(ji,jj) * xpar(ji,jj,jk)))
1470               !! frd(ji,jj) = (xthetam / fthetad(ji,jj)) * (fprd(ji,jj) / (fthetad(ji,jj) * xpar(ji,jj,jk)))
1471               frn(ji,jj) = (xthetam * fchn(ji,jj) * fnln(ji,jj) * ffln(ji,jj)       ) / (fthetan(ji,jj) + tiny(fthetan(ji,jj)))
1472               !! AXY (12/05/09): there's potentially a problem here; fsld, silicic acid
1473               !!   limitation, is used in the following line to regulate chlorophyll
1474               !!   growth in a manner that is inconsistent with its use in the regulation
1475               !!   of biomass growth; the Mongin term term used in growth is more complex
1476               !!   than the simple multiplicative function used below
1477               !! frd(ji,jj) = (xthetam * fchd(ji,jj) * fnld(ji,jj) * ffld(ji,jj) * fsld(ji,jj)) / (fthetad(ji,jj) + tiny(fthetad(ji,jj)))
1478               !! AXY (12/05/09): this replacement line uses the new variable, fsld2, to
1479               !!   regulate chlorophyll growth
1480               frd(ji,jj) = (xthetamd * fchd(ji,jj) * fnld(ji,jj) * ffld(ji,jj) * fsld2(ji,jj)) / (fthetad(ji,jj) + tiny(fthetad(ji,jj)))
1481
1482# if defined key_debug_medusa
1483               !! report chlorophyll calculations
1484               if (idf.eq.1.AND.idfval.eq.1) then
1485                  IF (lwp) write (numout,*) '------------------------------'
1486                  IF (lwp) write (numout,*) 'fthetan(',jk,') = ', fthetan(ji,jj)
1487                  IF (lwp) write (numout,*) 'fthetad(',jk,') = ', fthetad(ji,jj)
1488                  IF (lwp) write (numout,*) 'frn(',jk,')     = ', frn(ji,jj)
1489                  IF (lwp) write (numout,*) 'frd(',jk,')     = ', frd(ji,jj)
1490               endif
1491# endif
1492
1493               !!----------------------------------------------------------------------
1494               !! Zooplankton Grazing
1495               !! this code supplements the base grazing model with one that
1496               !! considers the C:N ratio of grazed food and balances this against
1497               !! the requirements of zooplankton growth; this model is derived
1498               !! from that of Anderson & Pondaven (2003)
1499               !!
1500               !! the current version of the code assumes a fixed C:N ratio for
1501               !! detritus (in contrast to Anderson & Pondaven, 2003), though the
1502               !! full equations are retained for future extension
1503               !!----------------------------------------------------------------------
1504               !!
1505               !!----------------------------------------------------------------------
1506               !! Microzooplankton first
1507               !!----------------------------------------------------------------------
1508               !!
1509               fmi1(ji,jj)    = (xkmi * xkmi) + (xpmipn * zphn(ji,jj) * zphn(ji,jj)) + (xpmid * zdet(ji,jj) * zdet(ji,jj))
1510               fmi(ji,jj)     = xgmi * zzmi(ji,jj) / fmi1(ji,jj)
1511               fgmipn(ji,jj)  = fmi(ji,jj) * xpmipn * zphn(ji,jj) * zphn(ji,jj)   !! grazing on non-diatoms
1512               fgmid(ji,jj)   = fmi(ji,jj) * xpmid  * zdet(ji,jj) * zdet(ji,jj)   !! grazing on detrital nitrogen
1513# if defined key_roam
1514               fgmidc(ji,jj)  = rsmall !acc
1515               IF ( zdet(ji,jj) .GT. rsmall ) fgmidc(ji,jj)  = (zdtc(ji,jj) / (zdet(ji,jj) + tiny(zdet(ji,jj)))) * fgmid(ji,jj)  !! grazing on detrital carbon
1516# else
1517               !! AXY (26/11/08): implicit detrital carbon change
1518               fgmidc(ji,jj)  = xthetad * fgmid(ji,jj)              !! grazing on detrital carbon
1519# endif
1520               !!
1521               !! which translates to these incoming N and C fluxes
1522               finmi(ji,jj)   = (1.0 - xphi) * (fgmipn(ji,jj) + fgmid(ji,jj))
1523               ficmi(ji,jj)   = (1.0 - xphi) * ((xthetapn * fgmipn(ji,jj)) + fgmidc(ji,jj))
1524               !!
1525               !! the ideal food C:N ratio for microzooplankton
1526               !! xbetan = 0.77; xthetaz = 5.625; xbetac = 0.64; xkc = 0.80
1527               fstarmi(ji,jj) = (xbetan * xthetazmi) / (xbetac * xkc)
1528               !!
1529               !! process these to determine proportioning of grazed N and C
1530               !! (since there is no explicit consideration of respiration,
1531               !! only growth and excretion are calculated here)
1532               fmith(ji,jj)   = (ficmi(ji,jj) / (finmi(ji,jj) + tiny(finmi(ji,jj))))
1533               if (fmith(ji,jj).ge.fstarmi(ji,jj)) then
1534                  fmigrow(ji,jj) = xbetan * finmi(ji,jj)
1535                  fmiexcr(ji,jj) = 0.0
1536               else
1537                  fmigrow(ji,jj) = (xbetac * xkc * ficmi(ji,jj)) / xthetazmi
1538                  fmiexcr(ji,jj) = ficmi(ji,jj) * ((xbetan / (fmith(ji,jj) + tiny(fmith(ji,jj)))) - ((xbetac * xkc) / xthetazmi))
1539               endif
1540# if defined key_roam
1541               fmiresp(ji,jj) = (xbetac * ficmi(ji,jj)) - (xthetazmi * fmigrow(ji,jj))
1542# endif
1543
1544# if defined key_debug_medusa
1545               !! report microzooplankton grazing
1546               if (idf.eq.1.AND.idfval.eq.1) then
1547                  IF (lwp) write (numout,*) '------------------------------'
1548                  IF (lwp) write (numout,*) 'fmi1(',jk,')    = ', fmi1(ji,jj)
1549                  IF (lwp) write (numout,*) 'fmi(',jk,')     = ', fmi(ji,jj)
1550                  IF (lwp) write (numout,*) 'fgmipn(',jk,')  = ', fgmipn(ji,jj)
1551                  IF (lwp) write (numout,*) 'fgmid(',jk,')   = ', fgmid(ji,jj)
1552                  IF (lwp) write (numout,*) 'fgmidc(',jk,')  = ', fgmidc(ji,jj)
1553                  IF (lwp) write (numout,*) 'finmi(',jk,')   = ', finmi(ji,jj)
1554                  IF (lwp) write (numout,*) 'ficmi(',jk,')   = ', ficmi(ji,jj)
1555                  IF (lwp) write (numout,*) 'fstarmi(',jk,') = ', fstarmi(ji,jj)
1556                  IF (lwp) write (numout,*) 'fmith(',jk,')   = ', fmith(ji,jj)
1557                  IF (lwp) write (numout,*) 'fmigrow(',jk,') = ', fmigrow(ji,jj)
1558                  IF (lwp) write (numout,*) 'fmiexcr(',jk,') = ', fmiexcr(ji,jj)
1559#  if defined key_roam
1560                  IF (lwp) write (numout,*) 'fmiresp(',jk,') = ', fmiresp(ji,jj)
1561#  endif
1562               endif
1563# endif
1564
1565               !!----------------------------------------------------------------------
1566               !! Mesozooplankton second
1567               !!----------------------------------------------------------------------
1568               !!
1569               fme1(ji,jj)    = (xkme * xkme) + (xpmepn * zphn(ji,jj) * zphn(ji,jj)) + (xpmepd * zphd(ji,jj) * zphd(ji,jj)) + & 
1570                         (xpmezmi * zzmi(ji,jj) * zzmi(ji,jj)) + (xpmed * zdet(ji,jj) * zdet(ji,jj))
1571               fme(ji,jj)     = xgme * zzme(ji,jj) / fme1(ji,jj)
1572               fgmepn(ji,jj)  = fme(ji,jj) * xpmepn  * zphn(ji,jj) * zphn(ji,jj)  !! grazing on non-diatoms
1573               fgmepd(ji,jj)  = fme(ji,jj) * xpmepd  * zphd(ji,jj) * zphd(ji,jj)  !! grazing on diatoms
1574               fgmepds(ji,jj) = fsin(ji,jj) * fgmepd(ji,jj)                !! grazing on diatom silicon
1575               fgmezmi(ji,jj) = fme(ji,jj) * xpmezmi * zzmi(ji,jj) * zzmi(ji,jj)  !! grazing on microzooplankton
1576               fgmed(ji,jj)   = fme(ji,jj) * xpmed   * zdet(ji,jj) * zdet(ji,jj)  !! grazing on detrital nitrogen
1577# if defined key_roam
1578               fgmedc(ji,jj)  = rsmall !acc
1579               IF ( zdet(ji,jj) .GT. rsmall ) fgmedc(ji,jj)  = (zdtc(ji,jj) / (zdet(ji,jj) + tiny(zdet(ji,jj)))) * fgmed(ji,jj)  !! grazing on detrital carbon
1580# else
1581               !! AXY (26/11/08): implicit detrital carbon change
1582               fgmedc(ji,jj)  = xthetad * fgmed(ji,jj)              !! grazing on detrital carbon
1583# endif
1584               !!
1585               !! which translates to these incoming N and C fluxes
1586               finme(ji,jj)   = (1.0 - xphi) * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj))
1587               ficme(ji,jj)   = (1.0 - xphi) * ((xthetapn * fgmepn(ji,jj)) + (xthetapd * fgmepd(ji,jj)) + &
1588                        (xthetazmi * fgmezmi(ji,jj)) + fgmedc(ji,jj))
1589               !!
1590               !! the ideal food C:N ratio for mesozooplankton
1591               !! xbetan = 0.77; xthetaz = 5.625; xbetac = 0.64; xkc = 0.80
1592               fstarme(ji,jj) = (xbetan * xthetazme) / (xbetac * xkc)
1593               !!
1594               !! process these to determine proportioning of grazed N and C
1595               !! (since there is no explicit consideration of respiration,
1596               !! only growth and excretion are calculated here)
1597               fmeth(ji,jj)   = (ficme(ji,jj) / (finme(ji,jj) + tiny(finme(ji,jj))))
1598               if (fmeth(ji,jj).ge.fstarme(ji,jj)) then
1599                  fmegrow(ji,jj) = xbetan * finme(ji,jj)
1600                  fmeexcr(ji,jj) = 0.0
1601               else
1602                  fmegrow(ji,jj) = (xbetac * xkc * ficme(ji,jj)) / xthetazme
1603                  fmeexcr(ji,jj) = ficme(ji,jj) * ((xbetan / (fmeth(ji,jj) + tiny(fmeth(ji,jj)))) - ((xbetac * xkc) / xthetazme))
1604               endif
1605# if defined key_roam
1606               fmeresp(ji,jj) = (xbetac * ficme(ji,jj)) - (xthetazme * fmegrow(ji,jj))
1607# endif
1608
1609# if defined key_debug_medusa
1610               !! report mesozooplankton grazing
1611               if (idf.eq.1.AND.idfval.eq.1) then
1612                  IF (lwp) write (numout,*) '------------------------------'
1613                  IF (lwp) write (numout,*) 'fme1(',jk,')    = ', fme1(ji,jj)
1614                  IF (lwp) write (numout,*) 'fme(',jk,')     = ', fme(ji,jj)
1615                  IF (lwp) write (numout,*) 'fgmepn(',jk,')  = ', fgmepn(ji,jj)
1616                  IF (lwp) write (numout,*) 'fgmepd(',jk,')  = ', fgmepd(ji,jj)
1617                  IF (lwp) write (numout,*) 'fgmepds(',jk,') = ', fgmepds(ji,jj)
1618                  IF (lwp) write (numout,*) 'fgmezmi(',jk,') = ', fgmezmi(ji,jj)
1619                  IF (lwp) write (numout,*) 'fgmed(',jk,')   = ', fgmed(ji,jj)
1620                  IF (lwp) write (numout,*) 'fgmedc(',jk,')  = ', fgmedc(ji,jj)
1621                  IF (lwp) write (numout,*) 'finme(',jk,')   = ', finme(ji,jj)
1622                  IF (lwp) write (numout,*) 'ficme(',jk,')   = ', ficme(ji,jj)
1623                  IF (lwp) write (numout,*) 'fstarme(',jk,') = ', fstarme(ji,jj)
1624                  IF (lwp) write (numout,*) 'fmeth(',jk,')   = ', fmeth(ji,jj)
1625                  IF (lwp) write (numout,*) 'fmegrow(',jk,') = ', fmegrow(ji,jj)
1626                  IF (lwp) write (numout,*) 'fmeexcr(',jk,') = ', fmeexcr(ji,jj)
1627#  if defined key_roam
1628                  IF (lwp) write (numout,*) 'fmeresp(',jk,') = ', fmeresp(ji,jj)
1629#  endif
1630               endif
1631# endif
1632
1633               fzmi_i(ji,jj)  = fzmi_i(ji,jj)  + fse3t(ji,jj,jk) * (  &
1634                  fgmipn(ji,jj) + fgmid(ji,jj) )
1635               fzmi_o(ji,jj)  = fzmi_o(ji,jj)  + fse3t(ji,jj,jk) * (  &
1636                  fmigrow(ji,jj) + (xphi * (fgmipn(ji,jj) + fgmid(ji,jj))) + fmiexcr(ji,jj) + ((1.0 - xbetan) * finmi(ji,jj)) )
1637               fzme_i(ji,jj)  = fzme_i(ji,jj)  + fse3t(ji,jj,jk) * (  &
1638                  fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj) )
1639               fzme_o(ji,jj)  = fzme_o(ji,jj)  + fse3t(ji,jj,jk) * (  &
1640                  fmegrow(ji,jj) + (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj))) + fmeexcr(ji,jj) + ((1.0 - xbetan) * finme(ji,jj)) )
1641
1642               !!----------------------------------------------------------------------
1643               !! Plankton metabolic losses
1644               !! Linear loss processes assumed to be metabolic in origin
1645               !!----------------------------------------------------------------------
1646               !!
1647               fdpn2(ji,jj)  = xmetapn  * zphn(ji,jj)
1648               fdpd2(ji,jj)  = xmetapd  * zphd(ji,jj)
1649               fdpds2(ji,jj) = xmetapd  * zpds(ji,jj)
1650               fdzmi2(ji,jj) = xmetazmi * zzmi(ji,jj)
1651               fdzme2(ji,jj) = xmetazme * zzme(ji,jj)
1652
1653               !!----------------------------------------------------------------------
1654               !! Plankton mortality losses
1655               !! EKP (26/02/09): phytoplankton hyperbolic mortality term introduced
1656               !! to improve performance in gyres
1657               !!----------------------------------------------------------------------
1658               !!
1659               !! non-diatom phytoplankton
1660               if (jmpn.eq.1) fdpn(ji,jj) = xmpn * zphn(ji,jj)               !! linear
1661               if (jmpn.eq.2) fdpn(ji,jj) = xmpn * zphn(ji,jj) * zphn(ji,jj)        !! quadratic
1662               if (jmpn.eq.3) fdpn(ji,jj) = xmpn * zphn(ji,jj) * &           !! hyperbolic
1663                  (zphn(ji,jj) / (xkphn + zphn(ji,jj)))
1664               if (jmpn.eq.4) fdpn(ji,jj) = xmpn * zphn(ji,jj) * &           !! sigmoid
1665                  ((zphn(ji,jj) * zphn(ji,jj)) / (xkphn + (zphn(ji,jj) * zphn(ji,jj))))
1666               !!
1667               !! diatom phytoplankton
1668               if (jmpd.eq.1) fdpd(ji,jj) = xmpd * zphd(ji,jj)               !! linear
1669               if (jmpd.eq.2) fdpd(ji,jj) = xmpd * zphd(ji,jj) * zphd(ji,jj)        !! quadratic
1670               if (jmpd.eq.3) fdpd(ji,jj) = xmpd * zphd(ji,jj) * &           !! hyperbolic
1671                  (zphd(ji,jj) / (xkphd + zphd(ji,jj)))
1672               if (jmpd.eq.4) fdpd(ji,jj) = xmpd * zphd(ji,jj) * &           !! sigmoid
1673                  ((zphd(ji,jj) * zphd(ji,jj)) / (xkphd + (zphd(ji,jj) * zphd(ji,jj))))
1674               fdpds(ji,jj) = fdpd(ji,jj) * fsin(ji,jj)
1675               !!
1676               !! microzooplankton
1677               if (jmzmi.eq.1) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj)            !! linear
1678               if (jmzmi.eq.2) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj) * zzmi(ji,jj)     !! quadratic
1679               if (jmzmi.eq.3) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj) * &        !! hyperbolic
1680                  (zzmi(ji,jj) / (xkzmi + zzmi(ji,jj)))
1681               if (jmzmi.eq.4) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj) * &        !! sigmoid
1682                  ((zzmi(ji,jj) * zzmi(ji,jj)) / (xkzmi + (zzmi(ji,jj) * zzmi(ji,jj))))
1683               !!
1684               !! mesozooplankton
1685               if (jmzme.eq.1) fdzme(ji,jj) = xmzme * zzme(ji,jj)            !! linear
1686               if (jmzme.eq.2) fdzme(ji,jj) = xmzme * zzme(ji,jj) * zzme(ji,jj)     !! quadratic
1687               if (jmzme.eq.3) fdzme(ji,jj) = xmzme * zzme(ji,jj) * &        !! hyperbolic
1688                  (zzme(ji,jj) / (xkzme + zzme(ji,jj)))
1689               if (jmzme.eq.4) fdzme(ji,jj) = xmzme * zzme(ji,jj) * &        !! sigmoid
1690                  ((zzme(ji,jj) * zzme(ji,jj)) / (xkzme + (zzme(ji,jj) * zzme(ji,jj))))
1691
1692               !!----------------------------------------------------------------------
1693               !! Detritus remineralisation
1694               !! Constant or temperature-dependent
1695               !!----------------------------------------------------------------------
1696               !!
1697               if (jmd.eq.1) then
1698                  !! temperature-dependent
1699                  fdd(ji,jj)  = xmd  * fun_T(ji,jj) * zdet(ji,jj)
1700# if defined key_roam
1701                  fddc(ji,jj) = xmdc * fun_T(ji,jj) * zdtc(ji,jj)
1702# endif
1703               elseif (jmd.eq.2) then
1704                  !! AXY (16/05/13): add in Q10-based parameterisation (def in nmlst)
1705                  !! temperature-dependent
1706                  fdd(ji,jj)  = xmd  * fun_Q10(ji,jj) * zdet(ji,jj)
1707#if defined key_roam
1708                  fddc(ji,jj) = xmdc * fun_Q10(ji,jj) * zdtc(ji,jj)
1709#endif
1710               else
1711                  !! temperature-independent
1712                  fdd(ji,jj)  = xmd  * zdet(ji,jj)
1713# if defined key_roam
1714                  fddc(ji,jj) = xmdc * zdtc(ji,jj)
1715# endif
1716               endif
1717               !!
1718               !! AXY (22/07/09): accelerate detrital remineralisation in the bottom box
1719               if ((jk.eq.mbathy(ji,jj)) .and. jsfd.eq.1) then
1720                  fdd(ji,jj)  = 1.0  * zdet(ji,jj)
1721# if defined key_roam
1722                  fddc(ji,jj) = 1.0  * zdtc(ji,jj)
1723# endif
1724               endif
1725               
1726# if defined key_debug_medusa
1727               !! report plankton mortality and remineralisation
1728               if (idf.eq.1.AND.idfval.eq.1) then
1729                  IF (lwp) write (numout,*) '------------------------------'
1730                  IF (lwp) write (numout,*) 'fdpn2(',jk,') = ', fdpn2(ji,jj)
1731                  IF (lwp) write (numout,*) 'fdpd2(',jk,') = ', fdpd2(ji,jj)
1732                  IF (lwp) write (numout,*) 'fdpds2(',jk,')= ', fdpds2(ji,jj)
1733                  IF (lwp) write (numout,*) 'fdzmi2(',jk,')= ', fdzmi2(ji,jj)
1734                  IF (lwp) write (numout,*) 'fdzme2(',jk,')= ', fdzme2(ji,jj)
1735                  IF (lwp) write (numout,*) 'fdpn(',jk,')  = ', fdpn(ji,jj)
1736                  IF (lwp) write (numout,*) 'fdpd(',jk,')  = ', fdpd(ji,jj)
1737                  IF (lwp) write (numout,*) 'fdpds(',jk,') = ', fdpds(ji,jj)
1738                  IF (lwp) write (numout,*) 'fdzmi(',jk,') = ', fdzmi(ji,jj)
1739                  IF (lwp) write (numout,*) 'fdzme(',jk,') = ', fdzme(ji,jj)
1740                  IF (lwp) write (numout,*) 'fdd(',jk,')   = ', fdd(ji,jj)
1741#  if defined key_roam
1742                  IF (lwp) write (numout,*) 'fddc(',jk,')  = ', fddc(ji,jj)
1743#  endif
1744               endif
1745# endif
1746
1747               !!----------------------------------------------------------------------
1748               !! Detritus addition to benthos
1749               !! If activated, slow detritus in the bottom box will enter the
1750               !! benthic pool
1751               !!----------------------------------------------------------------------
1752               !!
1753               if ((jk.eq.mbathy(ji,jj)) .and. jorgben.eq.1) then
1754                  !! this is the BOTTOM OCEAN BOX -> into the benthic pool!
1755                  !!
1756                  f_sbenin_n(ji,jj)  = (zdet(ji,jj) * vsed * 86400.)
1757                  f_sbenin_fe(ji,jj) = (zdet(ji,jj) * vsed * 86400. * xrfn)
1758# if defined key_roam
1759                  f_sbenin_c(ji,jj)  = (zdtc(ji,jj) * vsed * 86400.)
1760# else
1761                  f_sbenin_c(ji,jj)  = (zdet(ji,jj) * vsed * 86400. * xthetad)
1762# endif
1763               endif
1764
1765               !!----------------------------------------------------------------------
1766               !! Iron chemistry and fractionation
1767               !! following the Parekh et al. (2004) scheme adopted by the Met.
1768               !! Office, Medusa models total iron but considers "free" and
1769               !! ligand-bound forms for the purposes of scavenging (only "free"
1770               !! iron can be scavenged
1771               !!----------------------------------------------------------------------
1772               !!
1773               !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
1774               xFeT        = zfer(ji,jj) * 1.e3
1775               !!
1776               !! calculate fractionation (based on Diat-HadOCC; in turn based on Parekh et al., 2004)
1777               xb_coef_tmp = xk_FeL * (xLgT - xFeT) - 1.0
1778               xb2M4ac     = max(((xb_coef_tmp * xb_coef_tmp) + (4.0 * xk_FeL * xLgT)), 0.0)
1779               !!
1780               !! "free" ligand concentration
1781               xLgF        = 0.5 * (xb_coef_tmp + (xb2M4ac**0.5)) / xk_FeL
1782               !!
1783               !! ligand-bound iron concentration
1784               xFeL        = xLgT - xLgF
1785               !!
1786               !! "free" iron concentration (and convert to mmol Fe / m3)
1787               xFeF        = (xFeT - xFeL) * 1.e-3
1788               xFree(ji,jj)= xFeF / (zfer(ji,jj) + tiny(zfer(ji,jj)))
1789               !!
1790               !! scavenging of iron (multiple schemes); I'm only really happy with the
1791               !! first one at the moment - the others involve assumptions (sometimes
1792               !! guessed at by me) that are potentially questionable
1793               !!
1794               if (jiron.eq.1) then
1795                  !!----------------------------------------------------------------------
1796                  !! Scheme 1: Dutkiewicz et al. (2005)
1797                  !! This scheme includes a single scavenging term based solely on a
1798                  !! fixed rate and the availablility of "free" iron
1799                  !!----------------------------------------------------------------------
1800                  !!
1801                  ffescav(ji,jj)     = xk_sc_Fe * xFeF                     ! = mmol/m3/d
1802                  !!
1803                  !!----------------------------------------------------------------------
1804                  !!
1805                  !! Mick's code contains a further (optional) implicit "scavenging" of
1806                  !! iron that sets an upper bound on "free" iron concentration, and
1807                  !! essentially caps the concentration of total iron as xFeL + "free"
1808                  !! iron; since the former is constrained by a fixed total ligand
1809                  !! concentration (= 1.0 umol/m3), and the latter isn't allowed above
1810                  !! this upper bound, total iron is constrained to a maximum of ...
1811                  !!
1812                  !!    xFeL + min(xFeF, 0.3 umol/m3) = 1.0 + 0.3 = 1.3 umol / m3
1813                  !!
1814                  !! In Mick's code, the actual value of total iron is reset to this
1815                  !! sum (i.e. TFe = FeL + Fe'; but Fe' <= 0.3 umol/m3); this isn't
1816                  !! our favoured approach to tracer updating here (not least because
1817                  !! of the leapfrog), so here the amount scavenged is augmented by an
1818                  !! additional amount that serves to drag total iron back towards that
1819                  !! expected from this limitation on iron concentration ...
1820                  !!
1821                  xmaxFeF     = min((xFeF * 1.e3), 0.3)             ! = umol/m3
1822                  !!
1823                  !! Here, the difference between current total Fe and (FeL + Fe') is
1824                  !! calculated and added to the scavenging flux already calculated
1825                  !! above ...
1826                  !!
1827                  fdeltaFe    = (xFeT - (xFeL + xmaxFeF)) * 1.e-3   ! = mmol/m3
1828                  !!
1829                  !! This assumes that the "excess" iron is dissipated with a time-
1830                  !! scale of 1 day; seems reasonable to me ... (famous last words)
1831                  !!
1832                  ffescav(ji,jj)     = ffescav(ji,jj) + fdeltaFe                  ! = mmol/m3/d
1833                  !!
1834# if defined key_deep_fe_fix
1835                  !! AXY (17/01/13)
1836                  !! stop scavenging for iron concentrations below 0.5 umol / m3
1837                  !! at depths greater than 1000 m; this aims to end MEDUSA's
1838                  !! continual loss of iron at depth without impacting things
1839                  !! at the surface too much; the justification for this is that
1840                  !! it appears to be what Mick Follows et al. do in their work
1841                  !! (as evidenced by the iron initial condition they supplied
1842                  !! me with); to be honest, it looks like Follow et al. do this
1843                  !! at shallower depths than 1000 m, but I'll stick with this
1844                  !! for now; I suspect that this seemingly arbitrary approach
1845                  !! effectively "parameterises" the particle-based scavenging
1846                  !! rates that other models use (i.e. at depth there are no
1847                  !! sinking particles, so scavenging stops); it might be fun
1848                  !! justifying this in a paper though!
1849                  !!
1850                  if ((fsdepw(ji,jj,jk).gt.1000.) .and. (xFeT.lt.0.5)) then
1851                     ffescav(ji,jj) = 0.
1852                  endif
1853# endif
1854                  !!
1855               elseif (jiron.eq.2) then
1856                  !!----------------------------------------------------------------------
1857                  !! Scheme 2: Moore et al. (2004)
1858                  !! This scheme includes a single scavenging term that accounts for
1859                  !! both suspended and sinking particles in the water column; this
1860                  !! term scavenges total iron rather than "free" iron
1861                  !!----------------------------------------------------------------------
1862                  !!
1863                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
1864                  xFeT        = zfer(ji,jj) * 1.e3
1865                  !!
1866                  !! this has a base scavenging rate (12% / y) which is modified by local
1867                  !! particle concentration and sinking flux (and dust - but I'm ignoring
1868                  !! that here for now) and which is accelerated when Fe concentration gets
1869                  !! 0.6 nM (= 0.6 umol/m3 = 0.0006 mmol/m3), and decreased as concentrations
1870                  !! below 0.4 nM (= 0.4 umol/m3 = 0.0004 mmol/m3)
1871                  !!
1872                  !! base scavenging rate (0.12 / y)
1873                  fbase_scav = 0.12 / 365.25
1874                  !!
1875                  !! calculate sinking particle part of scaling factor
1876                  !! this takes local fast sinking carbon (mmol C / m2 / d) and
1877                  !! gets it into nmol C / cm3 / s ("rdt" below is the number of seconds in
1878                  !! a model timestep)
1879                  !!
1880                  !! fscal_sink = ffastc(ji,jj) * 1.e2 / (86400.)
1881                  !!
1882                  !! ... actually, re-reading Moore et al.'s equations, it looks like he uses
1883                  !! his sinking flux directly, without scaling it by time-step or anything,
1884                  !! so I'll copy this here ...
1885                  !!
1886                  fscal_sink = ffastc(ji,jj) * 1.e2
1887                  !!
1888                  !! calculate particle part of scaling factor
1889                  !! this totals up the carbon in suspended particles (Pn, Pd, Zmi, Zme, D),
1890                  !! which comes out in mmol C / m3 (= nmol C / cm3), and then multiplies it
1891                  !! by a magic factor, 0.002, to get it into nmol C / cm2 / s
1892                  !!
1893                  fscal_part = ((xthetapn * zphn(ji,jj)) + (xthetapd * zphd(ji,jj)) + (xthetazmi * zzmi(ji,jj)) + &
1894                  (xthetazme * zzme(ji,jj)) + (xthetad * zdet(ji,jj))) * 0.002
1895                  !!
1896                  !! calculate scaling factor for base scavenging rate
1897                  !! this uses the (now correctly scaled) sinking flux and standing
1898                  !! particle concentration, divides through by some sort of reference
1899                  !! value (= 0.0066 nmol C / cm2 / s) and then uses this, or not if its
1900                  !! too high, to rescale the base scavenging rate
1901                  !!
1902                  fscal_scav = fbase_scav * min(((fscal_sink + fscal_part) / 0.0066), 4.0)
1903                  !!
1904                  !! the resulting scavenging rate is then scaled further according to the
1905                  !! local iron concentration (i.e. diminished in low iron regions; enhanced
1906                  !! in high iron regions; less alone in intermediate iron regions)
1907                  !!
1908                  if (xFeT.lt.0.4) then
1909                     !!
1910                     !! low iron region
1911                     !!
1912                     fscal_scav = fscal_scav * (xFeT / 0.4)
1913                     !!
1914                  elseif (xFeT.gt.0.6) then
1915                     !!
1916                     !! high iron region
1917                     !!
1918                     fscal_scav = fscal_scav + ((xFeT / 0.6) * (6.0 / 1.4))
1919                     !!
1920                  else
1921                     !!
1922                     !! intermediate iron region: do nothing
1923                     !!
1924                  endif
1925                  !!
1926                  !! apply the calculated scavenging rate ...
1927                  !!
1928                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj)
1929                  !!
1930               elseif (jiron.eq.3) then
1931                  !!----------------------------------------------------------------------
1932                  !! Scheme 3: Moore et al. (2008)
1933                  !! This scheme includes a single scavenging term that accounts for
1934                  !! sinking particles in the water column, and includes organic C,
1935                  !! biogenic opal, calcium carbonate and dust in this (though the
1936                  !! latter is ignored here until I work out what units the incoming
1937                  !! "dust" flux is in); this term scavenges total iron rather than
1938                  !! "free" iron
1939                  !!----------------------------------------------------------------------
1940                  !!
1941                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
1942                  xFeT        = zfer(ji,jj) * 1.e3
1943                  !!
1944                  !! this has a base scavenging rate which is modified by local
1945                  !! particle sinking flux (including dust - but I'm ignoring that
1946                  !! here for now) and which is accelerated when Fe concentration
1947                  !! is > 0.6 nM (= 0.6 umol/m3 = 0.0006 mmol/m3), and decreased as
1948                  !! concentrations < 0.5 nM (= 0.5 umol/m3 = 0.0005 mmol/m3)
1949                  !!
1950                  !! base scavenging rate (Fe_b in paper; units may be wrong there)
1951                  fbase_scav = 0.00384 ! (ng)^-1 cm
1952                  !!
1953                  !! calculate sinking particle part of scaling factor; this converts
1954                  !! mmol / m2 / d fluxes of organic carbon, silicon and calcium
1955                  !! carbonate into ng / cm2 / s fluxes; it is assumed here that the
1956                  !! mass conversions simply consider the mass of the main element
1957                  !! (C, Si and Ca) and *not* the mass of the molecules that they are
1958                  !! part of; Moore et al. (2008) is unclear on the conversion that
1959                  !! should be used
1960                  !!
1961                  !! milli -> nano; mol -> gram; /m2 -> /cm2; /d -> /s
1962                  fscal_csink  = (ffastc(ji,jj)  * 1.e6 * xmassc  * 1.e-4 / 86400.)      ! ng C  / cm2 / s
1963                  fscal_sisink = (ffastsi(ji,jj) * 1.e6 * xmasssi * 1.e-4 / 86400.)      ! ng Si / cm2 / s
1964                  fscal_casink = (ffastca(ji,jj) * 1.e6 * xmassca * 1.e-4 / 86400.)      ! ng Ca / cm2 / s
1965                  !!
1966                  !! sum up these sinking fluxes and convert to ng / cm by dividing
1967                  !! through by a sinking rate of 100 m / d = 1.157 cm / s
1968                  fscal_sink   = ((fscal_csink * 6.) + fscal_sisink + fscal_casink) / &
1969                  (100. * 1.e3 / 86400)                                                  ! ng / cm
1970                  !!
1971                  !! now calculate the scavenging rate based upon the base rate and
1972                  !! this particle flux scaling; according to the published units,
1973                  !! the result actually has *no* units, but as it must be expressed
1974                  !! per unit time for it to make any sense, I'm assuming a missing
1975                  !! "per second"
1976                  fscal_scav = fbase_scav * fscal_sink                                   ! / s
1977                  !!
1978                  !! the resulting scavenging rate is then scaled further according to the
1979                  !! local iron concentration (i.e. diminished in low iron regions; enhanced
1980                  !! in high iron regions; less alone in intermediate iron regions)
1981                  !!
1982                  if (xFeT.lt.0.5) then
1983                     !!
1984                     !! low iron region (0.5 instead of the 0.4 in Moore et al., 2004)
1985                     !!
1986                     fscal_scav = fscal_scav * (xFeT / 0.5)
1987                     !!
1988                  elseif (xFeT.gt.0.6) then
1989                     !!
1990                     !! high iron region (functional form different in Moore et al., 2004)
1991                     !!
1992                     fscal_scav = fscal_scav + ((xFeT - 0.6) * 0.00904)
1993                     !!
1994                  else
1995                     !!
1996                     !! intermediate iron region: do nothing
1997                     !!
1998                  endif
1999                  !!
2000                  !! apply the calculated scavenging rate ...
2001                  !!
2002                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj)
2003                  !!
2004               elseif (jiron.eq.4) then
2005                  !!----------------------------------------------------------------------
2006                  !! Scheme 4: Galbraith et al. (2010)
2007                  !! This scheme includes two scavenging terms, one for organic,
2008                  !! particle-based scavenging, and another for inorganic scavenging;
2009                  !! both terms scavenge "free" iron only
2010                  !!----------------------------------------------------------------------
2011                  !!
2012                  !! Galbraith et al. (2010) present a more straightforward outline of
2013                  !! the scheme in Parekh et al. (2005) ...
2014                  !!
2015                  !! sinking particulate carbon available for scavenging
2016                  !! this assumes a sinking rate of 100 m / d (Moore & Braucher, 2008),
2017                  xCscav1     = (ffastc(ji,jj) * xmassc) / 100. ! = mg C / m3
2018                  !!
2019                  !! scale by Honeyman et al. (1981) exponent coefficient
2020                  !! multiply by 1.e-3 to express C flux in g C rather than mg C
2021                  xCscav2     = (xCscav1 * 1.e-3)**0.58
2022                  !!
2023                  !! multiply by Galbraith et al. (2010) scavenging rate
2024                  xk_org      = 0.5 ! ((g C m/3)^-1) / d
2025                  xORGscav    = xk_org * xCscav2 * xFeF
2026                  !!
2027                  !! Galbraith et al. (2010) also include an inorganic bit ...
2028                  !!
2029                  !! this occurs at a fixed rate, again based on the availability of
2030                  !! "free" iron
2031                  !!
2032                  !! k_inorg  = 1000 d**-1 nmol Fe**-0.5 kg**-0.5
2033                  !!
2034                  !! to implement this here, scale xFeF by 1026 to put in units of
2035                  !! umol/m3 which approximately equal nmol/kg
2036                  !!
2037                  xk_inorg    = 1000. ! ((nmol Fe / kg)^1.5)
2038                  xINORGscav  = (xk_inorg * (xFeF * 1026.)**1.5) * 1.e-3
2039                  !!
2040                  !! sum these two terms together
2041                  ffescav(ji,jj)     = xORGscav + xINORGscav
2042               else
2043                  !!----------------------------------------------------------------------
2044                  !! No Scheme: you coward!
2045                  !! This scheme puts its head in the sand and eskews any decision about
2046                  !! how iron is removed from the ocean; prepare to get deluged in iron
2047                  !! you fool!
2048                  !!----------------------------------------------------------------------
2049                  ffescav(ji,jj)     = 0.
2050               endif
2051
2052               !!----------------------------------------------------------------------
2053               !! Other iron cycle processes
2054               !!----------------------------------------------------------------------
2055               !!
2056               !! aeolian iron deposition
2057               if (jk.eq.1) then
2058                  !! zirondep   is in mmol-Fe / m2 / day
2059                  !! ffetop(ji,jj)     is in mmol-dissolved-Fe / m3 / day
2060                  ffetop(ji,jj)  = zirondep(ji,jj) * xfe_sol / fse3t(ji,jj,jk) 
2061               else
2062                  ffetop(ji,jj)  = 0.0
2063               endif
2064               !!
2065               !! seafloor iron addition
2066               !! AXY (10/07/12): amended to only apply sedimentary flux up to ~500 m down
2067               !! if (jk.eq.(mbathy(ji,jj)-1).AND.jk.lt.i1100) then
2068               if ((jk.eq.mbathy(ji,jj)).AND.jk.le.i0500) then
2069                  !! Moore et al. (2004) cite a coastal California value of 5 umol/m2/d, but adopt a
2070                  !! global value of 2 umol/m2/d for all areas < 1100 m; here we use this latter value
2071                  !! but apply it everywhere
2072                  !! AXY (21/07/09): actually, let's just apply it below 1100 m (levels 1-37)
2073                  ffebot(ji,jj)  = (xfe_sed / fse3t(ji,jj,jk))
2074               else
2075                  ffebot(ji,jj)  = 0.0
2076               endif
2077
2078               !! AXY (16/12/09): remove iron addition/removal processes
2079               !! For the purposes of the quarter degree run, the iron cycle is being pegged to the
2080               !! initial condition supplied by Mick Follows via restoration with a 30 day period;
2081               !! iron addition at the seafloor is still permitted with the idea that this extra
2082               !! iron will be removed by the restoration away from the source
2083               !! ffescav(ji,jj) = 0.0
2084               !! ffetop(ji,jj)  = 0.0
2085               !! ffebot(ji,jj)  = 0.0
2086
2087# if defined key_debug_medusa
2088               !! report miscellaneous calculations
2089               if (idf.eq.1.AND.idfval.eq.1) then
2090                  IF (lwp) write (numout,*) '------------------------------'
2091                  IF (lwp) write (numout,*) 'xfe_sol  = ', xfe_sol
2092                  IF (lwp) write (numout,*) 'xfe_mass = ', xfe_mass
2093                  IF (lwp) write (numout,*) 'ffetop(',jk,')  = ', ffetop(ji,jj)
2094                  IF (lwp) write (numout,*) 'ffebot(',jk,')  = ', ffebot(ji,jj)
2095                  IF (lwp) write (numout,*) 'xFree(',jk,')   = ', xFree(ji,jj)
2096                  IF (lwp) write (numout,*) 'ffescav(',jk,') = ', ffescav(ji,jj)
2097               endif
2098# endif
2099
2100               !!----------------------------------------------------------------------
2101               !! Miscellaneous
2102               !!----------------------------------------------------------------------
2103               !!
2104               !! diatom frustule dissolution
2105               fsdiss(ji,jj)  = xsdiss * zpds(ji,jj)
2106
2107# if defined key_debug_medusa
2108               !! report miscellaneous calculations
2109               if (idf.eq.1.AND.idfval.eq.1) then
2110                  IF (lwp) write (numout,*) '------------------------------'
2111                  IF (lwp) write (numout,*) 'fsdiss(',jk,')  = ', fsdiss(ji,jj)
2112               endif
2113# endif
2114
2115               !!----------------------------------------------------------------------
2116               !! Slow detritus creation
2117               !!----------------------------------------------------------------------
2118               !! this variable integrates the creation of slow sinking detritus
2119               !! to allow the split between fast and slow detritus to be
2120               !! diagnosed
2121               fslown(ji,jj)  = fdpn(ji,jj) + fdzmi(ji,jj) + ((1.0 - xfdfrac1) * fdpd(ji,jj)) + &
2122               ((1.0 - xfdfrac2) * fdzme(ji,jj)) + ((1.0 - xbetan) * (finmi(ji,jj) + finme(ji,jj)))
2123               !!
2124               !! this variable records the slow detrital sinking flux at this
2125               !! particular depth; it is used in the output of this flux at
2126               !! standard depths in the diagnostic outputs; needs to be
2127               !! adjusted from per second to per day because of parameter vsed
2128               fslownflux(ji,jj) = zdet(ji,jj) * vsed * 86400.
2129# if defined key_roam
2130               !!
2131               !! and the same for detrital carbon
2132               fslowc(ji,jj)  = (xthetapn * fdpn(ji,jj)) + (xthetazmi * fdzmi(ji,jj)) + &
2133               (xthetapd * (1.0 - xfdfrac1) * fdpd(ji,jj)) + &
2134               (xthetazme * (1.0 - xfdfrac2) * fdzme(ji,jj)) + &
2135               ((1.0 - xbetac) * (ficmi(ji,jj) + ficme(ji,jj)))
2136               !!
2137               !! this variable records the slow detrital sinking flux at this
2138               !! particular depth; it is used in the output of this flux at
2139               !! standard depths in the diagnostic outputs; needs to be
2140               !! adjusted from per second to per day because of parameter vsed
2141               fslowcflux(ji,jj) = zdtc(ji,jj) * vsed * 86400.
2142# endif
2143
2144               !!----------------------------------------------------------------------
2145               !! Nutrient regeneration
2146               !! this variable integrates total nitrogen regeneration down the
2147               !! watercolumn; its value is stored and output as a 2D diagnostic;
2148               !! the corresponding dissolution flux of silicon (from sources
2149               !! other than fast detritus) is also integrated; note that,
2150               !! confusingly, the linear loss terms from plankton compartments
2151               !! are labelled as fdX2 when one might have expected fdX or fdX1
2152               !!----------------------------------------------------------------------
2153               !!
2154               !! nitrogen
2155               fregen(ji,jj)   = (( (xphi * (fgmipn(ji,jj) + fgmid(ji,jj))) +                &  ! messy feeding
2156               (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj))) +           &  ! messy feeding
2157               fmiexcr(ji,jj) + fmeexcr(ji,jj) + fdd(ji,jj) +                                &  ! excretion + D remin.
2158               fdpn2(ji,jj) + fdpd2(ji,jj) + fdzmi2(ji,jj) + fdzme2(ji,jj)) * fse3t(ji,jj,jk))                    ! linear mortality
2159               !!
2160               !! silicon
2161               fregensi(ji,jj) = (( fsdiss(ji,jj) + ((1.0 - xfdfrac1) * fdpds(ji,jj)) +      &  ! dissolution + non-lin. mortality
2162               ((1.0 - xfdfrac3) * fgmepds(ji,jj)) +                           &  ! egestion by zooplankton
2163               fdpds2(ji,jj)) * fse3t(ji,jj,jk))                                             ! linear mortality
2164# if defined key_roam
2165               !!
2166               !! carbon
2167! Doesn't look this is used - marc 10/4/17
2168!               fregenc(ji,jj)  = (( (xphi * ((xthetapn * fgmipn(ji,jj)) + fgmidc(ji,jj))) +  &  ! messy feeding
2169!               (xphi * ((xthetapn * fgmepn(ji,jj)) + (xthetapd * fgmepd(ji,jj)) +     &  ! messy feeding
2170!               (xthetazmi * fgmezmi(ji,jj)) + fgmedc(ji,jj))) +                       &  ! messy feeding
2171!               fmiresp(ji,jj) + fmeresp(ji,jj) + fddc(ji,jj) +                               &  ! respiration + D remin.
2172!               (xthetapn * fdpn2(ji,jj)) + (xthetapd * fdpd2(ji,jj)) +                &  ! linear mortality
2173!               (xthetazmi * fdzmi2(ji,jj)) + (xthetazme * fdzme2(ji,jj))) * fse3t(ji,jj,jk))        ! linear mortality
2174# endif
2175
2176               !!----------------------------------------------------------------------
2177               !! Fast-sinking detritus terms
2178               !! "local" variables declared so that conservation can be checked;
2179               !! the calculated terms are added to the fast-sinking flux later on
2180               !! only after the flux entering this level has experienced some
2181               !! remineralisation
2182               !! note: these fluxes need to be scaled by the level thickness
2183               !!----------------------------------------------------------------------
2184               !!
2185               !! nitrogen:   diatom and mesozooplankton mortality
2186               ftempn(ji,jj)         = b0 * ((xfdfrac1 * fdpd(ji,jj))  + (xfdfrac2 * fdzme(ji,jj)))
2187               !!
2188               !! silicon:    diatom mortality and grazed diatoms
2189               ftempsi(ji,jj)        = b0 * ((xfdfrac1 * fdpds(ji,jj)) + (xfdfrac3 * fgmepds(ji,jj)))
2190               !!
2191               !! iron:       diatom and mesozooplankton mortality
2192               ftempfe(ji,jj)        = b0 * (((xfdfrac1 * fdpd(ji,jj)) + (xfdfrac2 * fdzme(ji,jj))) * xrfn)
2193               !!
2194               !! carbon:     diatom and mesozooplankton mortality
2195               ftempc(ji,jj)         = b0 * ((xfdfrac1 * xthetapd * fdpd(ji,jj)) + & 
2196                                (xfdfrac2 * xthetazme * fdzme(ji,jj)))
2197               !!
2198# if defined key_roam
2199               if (jrratio.eq.0) then
2200                  !! CaCO3:      latitudinally-based fraction of total primary production
2201                  !!               0.10 at equator; 0.02 at pole
2202                  fcaco3(ji,jj)         = xcaco3a + ((xcaco3b - xcaco3a) * ((90.0 - abs(gphit(ji,jj))) / 90.0))
2203               elseif (jrratio.eq.1) then
2204                  !! CaCO3:      Ridgwell et al. (2007) submodel, version 1
2205                  !!             this uses SURFACE omega calcite to regulate rain ratio
2206                  if (f_omcal(ji,jj).ge.1.0) then
2207                     fq1 = (f_omcal(ji,jj) - 1.0)**0.81
2208                  else
2209                     fq1 = 0.
2210                  endif
2211                  fcaco3(ji,jj) = xridg_r0 * fq1
2212               elseif (jrratio.eq.2) then
2213                  !! CaCO3:      Ridgwell et al. (2007) submodel, version 2
2214                  !!             this uses FULL 3D omega calcite to regulate rain ratio
2215                  if (f3_omcal(ji,jj,jk).ge.1.0) then
2216                     fq1 = (f3_omcal(ji,jj,jk) - 1.0)**0.81
2217                  else
2218                     fq1 = 0.
2219                  endif
2220                  fcaco3(ji,jj) = xridg_r0 * fq1
2221               endif
2222# else
2223               !! CaCO3:      latitudinally-based fraction of total primary production
2224               !!               0.10 at equator; 0.02 at pole
2225               fcaco3(ji,jj)         = xcaco3a + ((xcaco3b - xcaco3a) * ((90.0 - abs(gphit(ji,jj))) / 90.0))
2226# endif
2227               !! AXY (09/03/09): convert CaCO3 production from function of
2228               !! primary production into a function of fast-sinking material;
2229               !! technically, this is what Dunne et al. (2007) do anyway; they
2230               !! convert total primary production estimated from surface
2231               !! chlorophyll to an export flux for which they apply conversion
2232               !! factors to estimate the various elemental fractions (Si, Ca)
2233               ftempca(ji,jj)        = ftempc(ji,jj) * fcaco3(ji,jj)
2234
2235# if defined key_debug_medusa
2236               !! integrate total fast detritus production
2237               if (idf.eq.1) then
2238                  fifd_n(ji,jj)  = fifd_n(ji,jj)  + (ftempn(ji,jj)  * fse3t(ji,jj,jk))
2239                  fifd_si(ji,jj) = fifd_si(ji,jj) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))
2240                  fifd_fe(ji,jj) = fifd_fe(ji,jj) + (ftempfe(ji,jj) * fse3t(ji,jj,jk))
2241#  if defined key_roam
2242                  fifd_c(ji,jj)  = fifd_c(ji,jj)  + (ftempc(ji,jj)  * fse3t(ji,jj,jk))
2243#  endif
2244               endif
2245
2246               !! report quantities of fast-sinking detritus for each component
2247               if (idf.eq.1.AND.idfval.eq.1) then
2248                  IF (lwp) write (numout,*) '------------------------------'
2249                  IF (lwp) write (numout,*) 'fdpd(',jk,')    = ', fdpd(ji,jj)
2250                  IF (lwp) write (numout,*) 'fdzme(',jk,')   = ', fdzme(ji,jj)
2251                  IF (lwp) write (numout,*) 'ftempn(',jk,')  = ', ftempn(ji,jj)
2252                  IF (lwp) write (numout,*) 'ftempsi(',jk,') = ', ftempsi(ji,jj)
2253                  IF (lwp) write (numout,*) 'ftempfe(',jk,') = ', ftempfe(ji,jj)
2254                  IF (lwp) write (numout,*) 'ftempc(',jk,')  = ', ftempc(ji,jj)
2255                  IF (lwp) write (numout,*) 'ftempca(',jk,') = ', ftempca(ji,jj)
2256                  IF (lwp) write (numout,*) 'flat(',jk,')    = ', abs(gphit(ji,jj))
2257                  IF (lwp) write (numout,*) 'fcaco3(',jk,')  = ', fcaco3(ji,jj)
2258               endif
2259# endif
2260
2261               !!----------------------------------------------------------------------
2262               !! This version of MEDUSA offers a choice of three methods for
2263               !! handling the remineralisation of fast detritus.  All three
2264               !! do so in broadly the same way:
2265               !!
2266               !!   1.  Fast detritus is stored as a 2D array                   [ ffastX  ]
2267               !!   2.  Fast detritus is added level-by-level                   [ ftempX  ]
2268               !!   3.  Fast detritus is not remineralised in the top box       [ freminX ]
2269               !!   4.  Remaining fast detritus is remineralised in the bottom  [ fsedX   ]
2270               !!       box
2271               !!
2272               !! The three remineralisation methods are:
2273               !!   
2274               !!   1.  Ballast model (i.e. that published in Yool et al., 2011)
2275               !!  (1b. Ballast-sans-ballast model)
2276               !!   2.  Martin et al. (1987)
2277               !!   3.  Henson et al. (2011)
2278               !!
2279               !! The first of these couples C, N and Fe remineralisation to
2280               !! the remineralisation of particulate Si and CaCO3, but the
2281               !! latter two treat remineralisation of C, N, Fe, Si and CaCO3
2282               !! completely separately.  At present a switch within the code
2283               !! regulates which submodel is used, but this should be moved
2284               !! to the namelist file.
2285               !!
2286               !! The ballast-sans-ballast submodel is an original development
2287               !! feature of MEDUSA in which the ballast submodel's general
2288               !! framework and parameterisation is used, but in which there
2289               !! is no protection of organic material afforded by ballasting
2290               !! minerals.  While similar, it is not the same as the Martin
2291               !! et al. (1987) submodel.
2292               !!
2293               !! Since the three submodels behave the same in terms of
2294               !! accumulating sinking material and remineralising it all at
2295               !! the seafloor, these portions of the code below are common to
2296               !! all three.
2297               !!----------------------------------------------------------------------
2298
2299               if (jexport.eq.1) then
2300                  !!======================================================================
2301                  !! BALLAST SUBMODEL
2302                  !!======================================================================
2303                  !!
2304                  !!----------------------------------------------------------------------
2305                  !! Fast-sinking detritus fluxes, pt. 1: REMINERALISATION
2306                  !! aside from explicitly modelled, slow-sinking detritus, the
2307                  !! model includes an implicit representation of detrital
2308                  !! particles that sink too quickly to be modelled with
2309                  !! explicit state variables; this sinking flux is instead
2310                  !! instantaneously remineralised down the water column using
2311                  !! the version of Armstrong et al. (2002)'s ballast model
2312                  !! used by Dunne et al. (2007); the version of this model
2313                  !! here considers silicon and calcium carbonate ballast
2314                  !! minerals; this section of the code redistributes the fast
2315                  !! sinking material generated locally down the water column;
2316                  !! this differs from Dunne et al. (2007) in that fast sinking
2317                  !! material is distributed at *every* level below that it is
2318                  !! generated, rather than at every level below some fixed
2319                  !! depth; this scheme is also different in that sinking material
2320                  !! generated in one level is aggregated with that generated by
2321                  !! shallower levels; this should make the ballast model more
2322                  !! self-consistent (famous last words)
2323                  !!----------------------------------------------------------------------
2324                  !!
2325                  if (jk.eq.1) then
2326                     !! this is the SURFACE OCEAN BOX (no remineralisation)
2327                     !!
2328                     freminc(ji,jj)  = 0.0
2329                     freminn(ji,jj)  = 0.0
2330                     freminfe(ji,jj) = 0.0
2331                     freminsi(ji,jj) = 0.0
2332                     freminca(ji,jj) = 0.0
2333                  elseif (jk.le.mbathy(ji,jj)) then
2334                     !! this is an OCEAN BOX (remineralise some material)
2335                     !!
2336                     !! set up CCD depth to be used depending on user choice
2337                     if (jocalccd.eq.0) then
2338                        !! use default CCD field
2339                        fccd_dep(ji,jj) = ocal_ccd(ji,jj)
2340                     elseif (jocalccd.eq.1) then
2341                        !! use calculated CCD field
2342                        fccd_dep(ji,jj) = f2_ccd_cal(ji,jj)
2343                     endif
2344                     !!
2345                     !! === organic carbon ===
2346                     fq0      = ffastc(ji,jj)                        !! how much organic C enters this box        (mol)
2347                     if (iball.eq.1) then
2348                        fq1      = (fq0 * xmassc)                    !! how much it weighs                        (mass)
2349                        fq2      = (ffastca(ji,jj) * xmassca)        !! how much CaCO3 enters this box            (mass)
2350                        fq3      = (ffastsi(ji,jj) * xmasssi)        !! how much  opal enters this box            (mass)
2351                        fq4      = (fq2 * xprotca) + (fq3 * xprotsi) !! total protected organic C                 (mass)
2352                        !! this next term is calculated for C but used for N and Fe as well
2353                        !! it needs to be protected in case ALL C is protected
2354                        if (fq4.lt.fq1) then
2355                           fprotf(ji,jj)   = (fq4 / (fq1 + tiny(fq1)))      !! protected fraction of total organic C     (non-dim)
2356                        else
2357                           fprotf(ji,jj)   = 1.0                            !! all organic C is protected                (non-dim)
2358                        endif
2359                        fq5      = (1.0 - fprotf(ji,jj))                    !! unprotected fraction of total organic C   (non-dim)
2360                        fq6      = (fq0 * fq5)                       !! how much organic C is unprotected         (mol)
2361                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))     !! how much unprotected C leaves this box    (mol)
2362                        fq8      = (fq7 + (fq0 * fprotf(ji,jj)))            !! how much total C leaves this box          (mol)
2363                        freminc(ji,jj)  = (fq0 - fq8) / fse3t(ji,jj,jk)                !! C remineralisation in this box            (mol)
2364                        ffastc(ji,jj) = fq8                         
2365# if defined key_debug_medusa
2366                        !! report in/out/remin fluxes of carbon for this level
2367                           if (idf.eq.1.AND.idfval.eq.1) then
2368                              IF (lwp) write (numout,*) '------------------------------'
2369                              IF (lwp) write (numout,*) 'totalC(',jk,')  = ', fq1
2370                              IF (lwp) write (numout,*) 'prtctC(',jk,')  = ', fq4
2371                              IF (lwp) write (numout,*) 'fprotf(',jk,')  = ', fprotf(ji,jj)
2372                              IF (lwp) write (numout,*) '------------------------------'
2373                              IF (lwp) write (numout,*) 'IN   C(',jk,')  = ', fq0
2374                              IF (lwp) write (numout,*) 'LOST C(',jk,')  = ', freminc(ji,jj) * fse3t(ji,jj,jk)
2375                              IF (lwp) write (numout,*) 'OUT  C(',jk,')  = ', fq8
2376                              IF (lwp) write (numout,*) 'NEW  C(',jk,')  = ', ftempc(ji,jj) * fse3t(ji,jj,jk)
2377                           endif
2378# endif
2379                        else
2380                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))       !! how much organic C leaves this box        (mol)
2381                        freminc(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                !! C remineralisation in this box            (mol)
2382                        ffastc(ji,jj)  = fq1
2383                     endif
2384                     !!
2385                     !! === organic nitrogen ===
2386                     fq0      = ffastn(ji,jj)                        !! how much organic N enters this box        (mol)
2387                     if (iball.eq.1) then
2388                        fq5      = (1.0 - fprotf(ji,jj))                    !! unprotected fraction of total organic N   (non-dim)
2389                        fq6      = (fq0 * fq5)                       !! how much organic N is unprotected         (mol)
2390                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))     !! how much unprotected N leaves this box    (mol)
2391                        fq8      = (fq7 + (fq0 * fprotf(ji,jj)))            !! how much total N leaves this box          (mol)
2392                        freminn(ji,jj)  = (fq0 - fq8) / fse3t(ji,jj,jk)                !! N remineralisation in this box            (mol)
2393                        ffastn(ji,jj)  = fq8
2394# if defined key_debug_medusa
2395                        !! report in/out/remin fluxes of carbon for this level
2396                        if (idf.eq.1.AND.idfval.eq.1) then
2397                           IF (lwp) write (numout,*) '------------------------------'
2398                           IF (lwp) write (numout,*) 'totalN(',jk,')  = ', fq1
2399                           IF (lwp) write (numout,*) 'prtctN(',jk,')  = ', fq4
2400                           IF (lwp) write (numout,*) 'fprotf(',jk,')  = ', fprotf(ji,jj)
2401                           IF (lwp) write (numout,*) '------------------------------'
2402                           if (freminn(ji,jj) < 0.0) then
2403                              IF (lwp) write (numout,*) '** FREMIN ERROR **'
2404                           endif
2405                           IF (lwp) write (numout,*) 'IN   N(',jk,')  = ', fq0
2406                           IF (lwp) write (numout,*) 'LOST N(',jk,')  = ', freminn(ji,jj) * fse3t(ji,jj,jk)
2407                           IF (lwp) write (numout,*) 'OUT  N(',jk,')  = ', fq8
2408                           IF (lwp) write (numout,*) 'NEW  N(',jk,')  = ', ftempn(ji,jj) * fse3t(ji,jj,jk)
2409                        endif
2410# endif
2411                     else
2412                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))       !! how much organic N leaves this box        (mol)
2413                        freminn(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                !! N remineralisation in this box            (mol)
2414                        ffastn(ji,jj)  = fq1
2415                     endif
2416                     !!
2417                     !! === organic iron ===
2418                     fq0      = ffastfe(ji,jj)                       !! how much organic Fe enters this box       (mol)
2419                     if (iball.eq.1) then
2420                        fq5      = (1.0 - fprotf(ji,jj))                    !! unprotected fraction of total organic Fe  (non-dim)
2421                        fq6      = (fq0 * fq5)                       !! how much organic Fe is unprotected        (mol)
2422                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))     !! how much unprotected Fe leaves this box   (mol)
2423                        fq8      = (fq7 + (fq0 * fprotf(ji,jj)))            !! how much total Fe leaves this box         (mol)           
2424                        freminfe(ji,jj) = (fq0 - fq8) / fse3t(ji,jj,jk)                !! Fe remineralisation in this box           (mol)
2425                        ffastfe(ji,jj) = fq8
2426                     else
2427                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))       !! how much total Fe leaves this box         (mol)     
2428                        freminfe(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Fe remineralisation in this box           (mol)
2429                        ffastfe(ji,jj) = fq1
2430                     endif
2431                     !!
2432                     !! === biogenic silicon ===
2433                     fq0      = ffastsi(ji,jj)                       !! how much  opal centers this box           (mol)
2434                     fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastsi))         !! how much  opal leaves this box            (mol)
2435                     freminsi(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! Si remineralisation in this box           (mol)
2436                     ffastsi(ji,jj) = fq1
2437                     !!
2438                     !! === biogenic calcium carbonate ===
2439                     fq0      = ffastca(ji,jj)                       !! how much CaCO3 enters this box            (mol)
2440                     if (fsdepw(ji,jj,jk).le.fccd_dep(ji,jj)) then
2441                        !! whole grid cell above CCD
2442                        fq1      = fq0                               !! above lysocline, no Ca dissolves          (mol)
2443                        freminca(ji,jj) = 0.0                               !! above lysocline, no Ca dissolves          (mol)
2444                        fccd(ji,jj) = real(jk)                       !! which is the last level above the CCD?    (#)
2445                     elseif (fsdepw(ji,jj,jk).ge.fccd_dep(ji,jj)) then
2446                        !! whole grid cell below CCD
2447                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastca))      !! how much CaCO3 leaves this box            (mol)
2448                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2449                     else
2450                        !! partial grid cell below CCD
2451                        fq2      = fdep1(ji,jj) - fccd_dep(ji,jj)                  !! amount of grid cell below CCD             (m)
2452                        fq1      = fq0 * exp(-(fq2 / xfastca))       !! how much CaCO3 leaves this box            (mol)
2453                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2454                     endif
2455                     ffastca(ji,jj) = fq1 
2456                  else
2457                     !! this is BELOW THE LAST OCEAN BOX (do nothing)
2458                     freminc(ji,jj)  = 0.0
2459                     freminn(ji,jj)  = 0.0
2460                     freminfe(ji,jj) = 0.0
2461                     freminsi(ji,jj) = 0.0
2462                     freminca(ji,jj) = 0.0             
2463                  endif
2464
2465               elseif (jexport.eq.2.or.jexport.eq.3) then
2466                  if (jexport.eq.2) then
2467                     !!======================================================================
2468                     !! MARTIN ET AL. (1987) SUBMODEL
2469                     !!======================================================================
2470                     !!
2471                     !!----------------------------------------------------------------------
2472                     !! This submodel uses the classic Martin et al. (1987) curve
2473                     !! to determine the attenuation of fast-sinking detritus down
2474                     !! the water column.  All three organic elements, C, N and Fe,
2475                     !! are handled identically, and their quantities in sinking
2476                     !! particles attenuate according to a power relationship
2477                     !! governed by parameter "b".  This is assigned a canonical
2478                     !! value of -0.858.  Biogenic opal and calcium carbonate are
2479                     !! attentuated using the same function as in the ballast
2480                     !! submodel
2481                     !!----------------------------------------------------------------------
2482                     !!
2483                     fb_val = -0.858
2484                  elseif (jexport.eq.3) then
2485                     !!======================================================================
2486                     !! HENSON ET AL. (2011) SUBMODEL
2487                     !!======================================================================
2488                     !!
2489                     !!----------------------------------------------------------------------
2490                     !! This submodel reconfigures the Martin et al. (1987) curve by
2491                     !! allowing the "b" value to vary geographically.  Its value is
2492                     !! set, following Henson et al. (2011), as a function of local
2493                     !! sea surface temperature:
2494                     !!   b = -1.06 + (0.024 * SST)
2495                     !! This means that remineralisation length scales are longer in
2496                     !! warm, tropical areas and shorter in cold, polar areas.  This
2497                     !! does seem back-to-front (i.e. one would expect GREATER
2498                     !! remineralisation in warmer waters), but is an outcome of
2499                     !! analysis of sediment trap data, and it may reflect details
2500                     !! of ecosystem structure that pertain to particle production
2501                     !! rather than simply Q10.
2502                     !!----------------------------------------------------------------------
2503                     !!
2504                     fl_sst = tsn(ji,jj,1,jp_tem)
2505                     fb_val = -1.06 + (0.024 * fl_sst)
2506                  endif
2507                  !!   
2508                  if (jk.eq.1) then
2509                     !! this is the SURFACE OCEAN BOX (no remineralisation)
2510                     !!
2511                     freminc(ji,jj)  = 0.0
2512                     freminn(ji,jj)  = 0.0
2513                     freminfe(ji,jj) = 0.0
2514                     freminsi(ji,jj) = 0.0
2515                     freminca(ji,jj) = 0.0
2516                  elseif (jk.le.mbathy(ji,jj)) then
2517                     !! this is an OCEAN BOX (remineralise some material)
2518                     !!
2519                     !! === organic carbon ===
2520                     fq0      = ffastc(ji,jj)                        !! how much organic C enters this box        (mol)
2521                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)         !! how much organic C leaves this box        (mol)
2522                     freminc(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! C remineralisation in this box            (mol)
2523                     ffastc(ji,jj)  = fq1
2524                     !!
2525                     !! === organic nitrogen ===
2526                     fq0      = ffastn(ji,jj)                        !! how much organic N enters this box        (mol)
2527                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)         !! how much organic N leaves this box        (mol)
2528                     freminn(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! N remineralisation in this box            (mol)
2529                     ffastn(ji,jj)  = fq1
2530                     !!
2531                     !! === organic iron ===
2532                     fq0      = ffastfe(ji,jj)                       !! how much organic Fe enters this box       (mol)
2533                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)         !! how much organic Fe leaves this box       (mol)
2534                     freminfe(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! Fe remineralisation in this box           (mol)
2535                     ffastfe(ji,jj) = fq1
2536                     !!
2537                     !! === biogenic silicon ===
2538                     fq0      = ffastsi(ji,jj)                       !! how much  opal centers this box           (mol)
2539                     fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastsi))         !! how much  opal leaves this box            (mol)
2540                     freminsi(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! Si remineralisation in this box           (mol)
2541                     ffastsi(ji,jj) = fq1
2542                     !!
2543                     !! === biogenic calcium carbonate ===
2544                     fq0      = ffastca(ji,jj)                       !! how much CaCO3 enters this box            (mol)
2545                     if (fsdepw(ji,jj,jk).le.ocal_ccd(ji,jj)) then
2546                        !! whole grid cell above CCD
2547                        fq1      = fq0                               !! above lysocline, no Ca dissolves          (mol)
2548                        freminca(ji,jj) = 0.0                               !! above lysocline, no Ca dissolves          (mol)
2549                        fccd(ji,jj) = real(jk)                       !! which is the last level above the CCD?    (#)
2550                     elseif (fsdepw(ji,jj,jk).ge.ocal_ccd(ji,jj)) then
2551                        !! whole grid cell below CCD
2552                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastca))      !! how much CaCO3 leaves this box            (mol)
2553                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2554                     else
2555                        !! partial grid cell below CCD
2556                        fq2      = fdep1(ji,jj) - ocal_ccd(ji,jj)           !! amount of grid cell below CCD             (m)
2557                        fq1      = fq0 * exp(-(fq2 / xfastca))       !! how much CaCO3 leaves this box            (mol)
2558                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2559                     endif
2560                     ffastca(ji,jj) = fq1 
2561                  else
2562                     !! this is BELOW THE LAST OCEAN BOX (do nothing)
2563                     freminc(ji,jj)  = 0.0
2564                     freminn(ji,jj)  = 0.0
2565                     freminfe(ji,jj) = 0.0
2566                     freminsi(ji,jj) = 0.0
2567                     freminca(ji,jj) = 0.0             
2568                  endif
2569
2570               endif
2571
2572               !!----------------------------------------------------------------------
2573               !! Fast-sinking detritus fluxes, pt. 2: UPDATE FAST FLUXES
2574               !! here locally calculated additions to the fast-sinking flux are added
2575               !! to the total fast-sinking flux; this is done here such that material
2576               !! produced in a particular layer is only remineralised below this
2577               !! layer
2578               !!----------------------------------------------------------------------
2579               !!
2580               !! add sinking material generated in this layer to running totals
2581               !!
2582               !! === organic carbon ===                          (diatom and mesozooplankton mortality)
2583               ffastc(ji,jj)  = ffastc(ji,jj)  + (ftempc(ji,jj)  * fse3t(ji,jj,jk))
2584               !!
2585               !! === organic nitrogen ===                        (diatom and mesozooplankton mortality)
2586               ffastn(ji,jj)  = ffastn(ji,jj)  + (ftempn(ji,jj)  * fse3t(ji,jj,jk))
2587               !!
2588               !! === organic iron ===                            (diatom and mesozooplankton mortality)
2589               ffastfe(ji,jj) = ffastfe(ji,jj) + (ftempfe(ji,jj) * fse3t(ji,jj,jk))
2590               !!
2591               !! === biogenic silicon ===                        (diatom mortality and grazed diatoms)
2592               ffastsi(ji,jj) = ffastsi(ji,jj) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))
2593               !!
2594               !! === biogenic calcium carbonate ===              (latitudinally-based fraction of total primary production)
2595               ffastca(ji,jj) = ffastca(ji,jj) + (ftempca(ji,jj) * fse3t(ji,jj,jk))
2596
2597               !!----------------------------------------------------------------------
2598               !! Fast-sinking detritus fluxes, pt. 3: SEAFLOOR
2599               !! remineralise all remaining fast-sinking detritus to dissolved
2600               !! nutrients; the sedimentation fluxes calculated here allow the
2601               !! separation of what's remineralised sinking through the final
2602               !! ocean box from that which is added to the final box by the
2603               !! remineralisation of material that reaches the seafloor (i.e.
2604               !! the model assumes that *all* material that hits the seafloor
2605               !! is remineralised and that none is permanently buried; hey,
2606               !! this is a giant GCM model that can't be run for long enough
2607               !! to deal with burial fluxes!)
2608               !!
2609               !! in a change to this process, in part so that MEDUSA behaves
2610               !! a little more like ERSEM et al., fast-sinking detritus (N, Fe
2611               !! and C) is converted to slow sinking detritus at the seafloor
2612               !! instead of being remineralised; the rationale is that in
2613               !! shallower shelf regions (... that are not fully mixed!) this
2614               !! allows the detrital material to return slowly to dissolved
2615               !! nutrient rather than instantaneously as now; the alternative
2616               !! would be to explicitly handle seafloor organic material - a
2617               !! headache I don't wish to experience at this point; note that
2618               !! fast-sinking Si and Ca detritus is just remineralised as
2619               !! per usual
2620               !!
2621               !! AXY (13/01/12)
2622               !! in a further change to this process, again so that MEDUSA is
2623               !! a little more like ERSEM et al., material that reaches the
2624               !! seafloor can now be added to sediment pools and stored for
2625               !! slow release; there are new 2D arrays for organic nitrogen,
2626               !! iron and carbon and inorganic silicon and carbon that allow
2627               !! fast and slow detritus that reaches the seafloor to be held
2628               !! and released back to the water column more slowly; these arrays
2629               !! are transferred via the tracer restart files between repeat
2630               !! submissions of the model
2631               !!----------------------------------------------------------------------
2632               !!
2633               ffast2slowc(ji,jj)  = 0.0
2634               ffast2slown(ji,jj)  = 0.0
2635! I don't think this is used - marc 10/4/17
2636!               ffast2slowfe(ji,jj) = 0.0
2637               !!
2638               if (jk.eq.mbathy(ji,jj)) then
2639                  !! this is the BOTTOM OCEAN BOX (remineralise everything)
2640                  !!
2641                  !! AXY (17/01/12): tweaked to include benthos pools
2642                  !!
2643                  !! === organic carbon ===
2644                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
2645                     freminc(ji,jj)  = freminc(ji,jj) + (ffastc(ji,jj) / fse3t(ji,jj,jk))    !! C remineralisation in this box            (mol/m3)
2646                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
2647                     ffast2slowc(ji,jj) = ffastc(ji,jj) / fse3t(ji,jj,jk)             !! fast C -> slow C                          (mol/m3)
2648                     fslowc(ji,jj)      = fslowc(ji,jj) + ffast2slowc(ji,jj)
2649                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
2650                     f_fbenin_c(ji,jj)  = ffastc(ji,jj)             !! fast C -> benthic C                       (mol/m2)
2651                  endif
2652                  fsedc(ji,jj)   = ffastc(ji,jj)                          !! record seafloor C                         (mol/m2)
2653                  ffastc(ji,jj)  = 0.0
2654                  !!
2655                  !! === organic nitrogen ===
2656                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
2657                     freminn(ji,jj)  = freminn(ji,jj) + (ffastn(ji,jj) / fse3t(ji,jj,jk))    !! N remineralisation in this box            (mol/m3)
2658                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
2659                     ffast2slown(ji,jj) = ffastn(ji,jj) / fse3t(ji,jj,jk)             !! fast N -> slow N                          (mol/m3)
2660                     fslown(ji,jj)      = fslown(ji,jj) + ffast2slown(ji,jj)
2661                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
2662                     f_fbenin_n(ji,jj)  = ffastn(ji,jj)             !! fast N -> benthic N                       (mol/m2)
2663                  endif
2664                  fsedn(ji,jj)   = ffastn(ji,jj)                          !! record seafloor N                         (mol/m2)
2665                  ffastn(ji,jj)  = 0.0
2666                  !!
2667                  !! === organic iron ===
2668                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
2669                     freminfe(ji,jj) = freminfe(ji,jj) + (ffastfe(ji,jj) / fse3t(ji,jj,jk))  !! Fe remineralisation in this box           (mol/m3)
2670! I don't think ffast2slowfe is used - marc 10/4/17
2671!                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
2672!                     ffast2slowfe(ji,jj) = ffastn(ji,jj) / fse3t(ji,jj,jk)            !! fast Fe -> slow Fe                        (mol/m3)
2673                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
2674                     f_fbenin_fe(ji,jj) = ffastfe(ji,jj)            !! fast Fe -> benthic Fe                     (mol/m2)
2675                  endif
2676                  fsedfe(ji,jj)  = ffastfe(ji,jj)                         !! record seafloor Fe                        (mol/m2)
2677                  ffastfe(ji,jj) = 0.0
2678                  !!
2679                  !! === biogenic silicon ===
2680                  if (jinorgben.eq.0) then
2681                     freminsi(ji,jj) = freminsi(ji,jj) + (ffastsi(ji,jj) / fse3t(ji,jj,jk))  !! Si remineralisation in this box           (mol/m3)
2682                  elseif (jinorgben.eq.1) then
2683                     f_fbenin_si(ji,jj) = ffastsi(ji,jj)            !! fast Si -> benthic Si                     (mol/m2)
2684                  endif
2685                  fsedsi(ji,jj)   = ffastsi(ji,jj)                         !! record seafloor Si                        (mol/m2)
2686                  ffastsi(ji,jj) = 0.0
2687                  !!
2688                  !! === biogenic calcium carbonate ===
2689                  if (jinorgben.eq.0) then
2690                     freminca(ji,jj) = freminca(ji,jj) + (ffastca(ji,jj) / fse3t(ji,jj,jk))  !! Ca remineralisation in this box           (mol/m3)
2691                  elseif (jinorgben.eq.1) then
2692                     f_fbenin_ca(ji,jj) = ffastca(ji,jj)            !! fast Ca -> benthic Ca                     (mol/m2)
2693                  endif
2694                  fsedca(ji,jj)   = ffastca(ji,jj)                         !! record seafloor Ca                        (mol/m2)
2695                  ffastca(ji,jj) = 0.0
2696               endif
2697
2698# if defined key_debug_medusa
2699               if (idf.eq.1) then
2700                  !!----------------------------------------------------------------------
2701                  !! Integrate total fast detritus remineralisation
2702                  !!----------------------------------------------------------------------
2703                  !!
2704                  fofd_n(ji,jj)  = fofd_n(ji,jj)  + (freminn(ji,jj)  * fse3t(ji,jj,jk))
2705                  fofd_si(ji,jj) = fofd_si(ji,jj) + (freminsi(ji,jj) * fse3t(ji,jj,jk))
2706                  fofd_fe(ji,jj) = fofd_fe(ji,jj) + (freminfe(ji,jj) * fse3t(ji,jj,jk))
2707#  if defined key_roam
2708                  fofd_c(ji,jj)  = fofd_c(ji,jj)  + (freminc(ji,jj)  * fse3t(ji,jj,jk))
2709#  endif
2710               endif
2711# endif
2712
2713               !!----------------------------------------------------------------------
2714               !! Sort out remineralisation tally of fast-sinking detritus
2715               !!----------------------------------------------------------------------
2716               !!
2717               !! update fast-sinking regeneration arrays
2718               fregenfast(ji,jj)   = fregenfast(ji,jj)   + (freminn(ji,jj)  * fse3t(ji,jj,jk))
2719               fregenfastsi(ji,jj) = fregenfastsi(ji,jj) + (freminsi(ji,jj) * fse3t(ji,jj,jk))
2720# if defined key_roam
2721               fregenfastc(ji,jj)  = fregenfastc(ji,jj)  + (freminc(ji,jj)  * fse3t(ji,jj,jk))
2722# endif
2723
2724               !!----------------------------------------------------------------------
2725               !! Benthic remineralisation fluxes
2726               !!----------------------------------------------------------------------
2727               !!
2728               if (jk.eq.mbathy(ji,jj)) then
2729                  !!
2730                  !! organic components
2731                  if (jorgben.eq.1) then
2732                     f_benout_n(ji,jj)  = xsedn  * zn_sed_n(ji,jj)
2733                     f_benout_fe(ji,jj) = xsedfe * zn_sed_fe(ji,jj)
2734                     f_benout_c(ji,jj)  = xsedc  * zn_sed_c(ji,jj)
2735                  endif
2736                  !!
2737                  !! inorganic components
2738                  if (jinorgben.eq.1) then
2739                     f_benout_si(ji,jj) = xsedsi * zn_sed_si(ji,jj)
2740                     f_benout_ca(ji,jj) = xsedca * zn_sed_ca(ji,jj)
2741                     !!
2742                     !! account for CaCO3 that dissolves when it shouldn't
2743                     if ( fsdepw(ji,jj,jk) .le. fccd_dep(ji,jj) ) then
2744                        f_benout_lyso_ca(ji,jj) = xsedca * zn_sed_ca(ji,jj)
2745                     endif
2746                  endif
2747               endif
2748               CALL flush(numout)
2749
2750               !!======================================================================
2751               !! LOCAL GRID CELL TRENDS
2752               !!======================================================================
2753               !!
2754               !!----------------------------------------------------------------------
2755               !! Determination of trends
2756               !!----------------------------------------------------------------------
2757               !!
2758               !!----------------------------------------------------------------------
2759               !! chlorophyll
2760               btra(ji,jj,jpchn) = b0 * ( &
2761                 + ((frn(ji,jj) * fprn(ji,jj) * zphn(ji,jj)) - fgmipn(ji,jj) - fgmepn(ji,jj) - fdpn(ji,jj) - fdpn2(ji,jj)) * (fthetan(ji,jj) / xxi) )
2762               btra(ji,jj,jpchd) = b0 * ( &
2763                 + ((frd(ji,jj) * fprd(ji,jj) * zphd(ji,jj)) - fgmepd(ji,jj) - fdpd(ji,jj) - fdpd2(ji,jj)) * (fthetad(ji,jj) / xxi) )
2764               !!
2765               !!----------------------------------------------------------------------
2766               !! phytoplankton
2767               btra(ji,jj,jpphn) = b0 * ( &
2768                 + (fprn(ji,jj) * zphn(ji,jj)) - fgmipn(ji,jj) - fgmepn(ji,jj) - fdpn(ji,jj) - fdpn2(ji,jj) )
2769               btra(ji,jj,jpphd) = b0 * ( &
2770                 + (fprd(ji,jj) * zphd(ji,jj)) - fgmepd(ji,jj) - fdpd(ji,jj) - fdpd2(ji,jj) )
2771               btra(ji,jj,jppds) = b0 * ( &
2772                 + (fprds(ji,jj) * zpds(ji,jj)) - fgmepds(ji,jj) - fdpds(ji,jj) - fsdiss(ji,jj) - fdpds2(ji,jj) )
2773               !!
2774               !!----------------------------------------------------------------------
2775               !! zooplankton
2776               btra(ji,jj,jpzmi) = b0 * ( &
2777                 + fmigrow(ji,jj) - fgmezmi(ji,jj) - fdzmi(ji,jj) - fdzmi2(ji,jj) )
2778               btra(ji,jj,jpzme) = b0 * ( &
2779                 + fmegrow(ji,jj) - fdzme(ji,jj) - fdzme2(ji,jj) )
2780               !!
2781               !!----------------------------------------------------------------------
2782               !! detritus
2783               btra(ji,jj,jpdet) = b0 * ( &
2784                 + fdpn(ji,jj) + ((1.0 - xfdfrac1) * fdpd(ji,jj))              &  ! mort. losses
2785                 + fdzmi(ji,jj) + ((1.0 - xfdfrac2) * fdzme(ji,jj))            &  ! mort. losses
2786                 + ((1.0 - xbetan) * (finmi(ji,jj) + finme(ji,jj)))            &  ! assim. inefficiency
2787                 - fgmid(ji,jj) - fgmed(ji,jj) - fdd(ji,jj)                           &  ! grazing and remin.
2788                 + ffast2slown(ji,jj) )                                    ! seafloor fast->slow
2789               !!
2790               !!----------------------------------------------------------------------
2791               !! dissolved inorganic nitrogen nutrient
2792               fn_cons = 0.0  &
2793                 - (fprn(ji,jj) * zphn(ji,jj)) - (fprd(ji,jj) * zphd(ji,jj))                    ! primary production
2794               fn_prod = 0.0  &
2795                 + (xphi * (fgmipn(ji,jj) + fgmid(ji,jj)))                     &  ! messy feeding remin.
2796                 + (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj)))  &  ! messy feeding remin.
2797                 + fmiexcr(ji,jj) + fmeexcr(ji,jj) + fdd(ji,jj) + freminn(ji,jj)             &  ! excretion and remin.
2798                 + fdpn2(ji,jj) + fdpd2(ji,jj) + fdzmi2(ji,jj) + fdzme2(ji,jj)                  ! metab. losses
2799               !!
2800               !! riverine flux
2801               if ( jriver_n .gt. 0 ) then
2802                  f_riv_loc_n(ji,jj) = f_riv_n(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2803                  fn_prod = fn_prod + f_riv_loc_n(ji,jj)
2804               endif
2805               !! 
2806               !! benthic remineralisation
2807               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2808                  fn_prod = fn_prod + (f_benout_n(ji,jj) / fse3t(ji,jj,jk))
2809               endif
2810               !!
2811               btra(ji,jj,jpdin) = b0 * ( &
2812                 fn_prod + fn_cons )
2813               !!
2814               fnit_cons(ji,jj) = fnit_cons(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! consumption of dissolved nitrogen
2815                 fn_cons ) )
2816               fnit_prod(ji,jj) = fnit_prod(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! production of dissolved nitrogen
2817                 fn_prod ) )
2818               !!
2819               !!----------------------------------------------------------------------
2820               !! dissolved silicic acid nutrient
2821               fs_cons = 0.0  &
2822                 - (fprds(ji,jj) * zpds(ji,jj))                                   ! opal production
2823               fs_prod = 0.0  &
2824                 + fsdiss(ji,jj)                                        &  ! opal dissolution
2825                 + ((1.0 - xfdfrac1) * fdpds(ji,jj))                    &  ! mort. loss
2826                 + ((1.0 - xfdfrac3) * fgmepds(ji,jj))                  &  ! egestion of grazed Si
2827                 + freminsi(ji,jj) + fdpds2(ji,jj)                                ! fast diss. and metab. losses
2828               !!
2829               !! riverine flux
2830               if ( jriver_si .gt. 0 ) then
2831                  f_riv_loc_si(ji,jj) = f_riv_si(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2832                  fs_prod = fs_prod + f_riv_loc_si(ji,jj)
2833               endif
2834               !! 
2835               !! benthic remineralisation
2836               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then
2837                  fs_prod = fs_prod + (f_benout_si(ji,jj) / fse3t(ji,jj,jk))
2838               endif
2839               !!
2840               btra(ji,jj,jpsil) = b0 * ( &
2841                 fs_prod + fs_cons )
2842               !!
2843               fsil_cons(ji,jj) = fsil_cons(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! consumption of dissolved silicon
2844                 fs_cons ) )
2845               fsil_prod(ji,jj) = fsil_prod(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! production of dissolved silicon
2846                 fs_prod ) )
2847               !!
2848               !!----------------------------------------------------------------------
2849               !! dissolved "iron" nutrient
2850               btra(ji,jj,jpfer) = b0 * ( &
2851               + (xrfn * btra(ji,jj,jpdin)) + ffetop(ji,jj) + ffebot(ji,jj) - ffescav(ji,jj) )
2852
2853# if defined key_roam
2854               !!
2855               !!----------------------------------------------------------------------
2856               !! AXY (26/11/08): implicit detrital carbon change
2857               btra(ji,jj,jpdtc) = b0 * ( &
2858                 + (xthetapn * fdpn(ji,jj)) + ((1.0 - xfdfrac1) * (xthetapd * fdpd(ji,jj)))      &  ! mort. losses
2859                 + (xthetazmi * fdzmi(ji,jj)) + ((1.0 - xfdfrac2) * (xthetazme * fdzme(ji,jj)))  &  ! mort. losses
2860                 + ((1.0 - xbetac) * (ficmi(ji,jj) + ficme(ji,jj)))                              &  ! assim. inefficiency
2861                 - fgmidc(ji,jj) - fgmedc(ji,jj) - fddc(ji,jj)                                          &  ! grazing and remin.
2862                 + ffast2slowc(ji,jj) )                                                      ! seafloor fast->slow
2863               !!
2864               !!----------------------------------------------------------------------
2865               !! dissolved inorganic carbon
2866               fc_cons = 0.0  &
2867                 - (xthetapn * fprn(ji,jj) * zphn(ji,jj)) - (xthetapd * fprd(ji,jj) * zphd(ji,jj))                ! primary production
2868               fc_prod = 0.0  &
2869                 + (xthetapn * xphi * fgmipn(ji,jj)) + (xphi * fgmidc(ji,jj))                    &  ! messy feeding remin
2870                 + (xthetapn * xphi * fgmepn(ji,jj)) + (xthetapd * xphi * fgmepd(ji,jj))         &  ! messy feeding remin
2871                 + (xthetazmi * xphi * fgmezmi(ji,jj)) + (xphi * fgmedc(ji,jj))                  &  ! messy feeding remin
2872                 + fmiresp(ji,jj) + fmeresp(ji,jj) + fddc(ji,jj) + freminc(ji,jj) + (xthetapn * fdpn2(ji,jj))         &  ! resp., remin., losses
2873                 + (xthetapd * fdpd2(ji,jj)) + (xthetazmi * fdzmi2(ji,jj))                       &  ! losses
2874                 + (xthetazme * fdzme2(ji,jj))                                               ! losses
2875               !!
2876               !! riverine flux
2877               if ( jriver_c .gt. 0 ) then
2878                  f_riv_loc_c(ji,jj) = f_riv_c(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2879                  fc_prod = fc_prod + f_riv_loc_c(ji,jj)
2880               endif
2881               !! 
2882               !! benthic remineralisation
2883               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2884                  fc_prod = fc_prod + (f_benout_c(ji,jj) / fse3t(ji,jj,jk))
2885               endif
2886               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then
2887                  fc_prod = fc_prod + (f_benout_ca(ji,jj) / fse3t(ji,jj,jk))
2888               endif
2889               !!
2890               !! community respiration (does not include CaCO3 terms - obviously!)
2891               fcomm_resp(ji,jj) = fcomm_resp(ji,jj) + fc_prod
2892               !!
2893               !! CaCO3
2894               fc_prod = fc_prod - ftempca(ji,jj) + freminca(ji,jj)
2895               !!
2896               !! riverine flux
2897               if ( jk .eq. 1 .and. jriver_c .gt. 0 ) then
2898                  fc_prod = fc_prod + f_riv_c(ji,jj)
2899               endif
2900               !!
2901               btra(ji,jj,jpdic) = b0 * ( &
2902                 fc_prod + fc_cons )
2903               !!
2904               fcar_cons(ji,jj) = fcar_cons(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! consumption of dissolved carbon
2905                 fc_cons ) )
2906               fcar_prod(ji,jj) = fcar_prod(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! production of dissolved carbon
2907                 fc_prod ) )
2908               !!
2909               !!----------------------------------------------------------------------
2910               !! alkalinity
2911               fa_prod = 0.0  &
2912                 + (2.0 * freminca(ji,jj))                                                   ! CaCO3 dissolution
2913               fa_cons = 0.0  &
2914                 - (2.0 * ftempca(ji,jj))                                                    ! CaCO3 production
2915               !!
2916               !! riverine flux
2917               if ( jriver_alk .gt. 0 ) then
2918                  f_riv_loc_alk(ji,jj) = f_riv_alk(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2919                  fa_prod = fa_prod + f_riv_loc_alk(ji,jj)
2920               endif
2921               !! 
2922               !! benthic remineralisation
2923               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then
2924                  fa_prod = fa_prod + (2.0 * f_benout_ca(ji,jj) / fse3t(ji,jj,jk))
2925               endif
2926               !!
2927               btra(ji,jj,jpalk) = b0 * ( &
2928                 fa_prod + fa_cons )
2929               !!
2930               !!----------------------------------------------------------------------
2931               !! oxygen (has protection at low O2 concentrations; OCMIP-2 style)
2932               fo2_prod(ji,jj) = 0.0 &
2933                 + (xthetanit * fprn(ji,jj) * zphn(ji,jj))                                      & ! Pn primary production, N
2934                 + (xthetanit * fprd(ji,jj) * zphd(ji,jj))                                      & ! Pd primary production, N
2935                 + (xthetarem * xthetapn * fprn(ji,jj) * zphn(ji,jj))                           & ! Pn primary production, C
2936                 + (xthetarem * xthetapd * fprd(ji,jj) * zphd(ji,jj))                             ! Pd primary production, C
2937               fo2_ncons(ji,jj) = 0.0 &
2938                 - (xthetanit * xphi * fgmipn(ji,jj))                                    & ! Pn messy feeding remin., N
2939                 - (xthetanit * xphi * fgmid(ji,jj))                                     & ! D  messy feeding remin., N
2940                 - (xthetanit * xphi * fgmepn(ji,jj))                                    & ! Pn messy feeding remin., N
2941                 - (xthetanit * xphi * fgmepd(ji,jj))                                    & ! Pd messy feeding remin., N
2942                 - (xthetanit * xphi * fgmezmi(ji,jj))                                   & ! Zi messy feeding remin., N
2943                 - (xthetanit * xphi * fgmed(ji,jj))                                     & ! D  messy feeding remin., N
2944                 - (xthetanit * fmiexcr(ji,jj))                                          & ! microzoo excretion, N
2945                 - (xthetanit * fmeexcr(ji,jj))                                          & ! mesozoo  excretion, N
2946                 - (xthetanit * fdd(ji,jj))                                              & ! slow detritus remin., N
2947                 - (xthetanit * freminn(ji,jj))                                          & ! fast detritus remin., N
2948                 - (xthetanit * fdpn2(ji,jj))                                            & ! Pn  losses, N
2949                 - (xthetanit * fdpd2(ji,jj))                                            & ! Pd  losses, N
2950                 - (xthetanit * fdzmi2(ji,jj))                                           & ! Zmi losses, N
2951                 - (xthetanit * fdzme2(ji,jj))                                             ! Zme losses, N
2952               !! 
2953               !! benthic remineralisation
2954               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2955                  fo2_ncons(ji,jj) = fo2_ncons(ji,jj) - (xthetanit * f_benout_n(ji,jj) / fse3t(ji,jj,jk))
2956               endif
2957               fo2_ccons(ji,jj) = 0.0 &
2958                 - (xthetarem * xthetapn * xphi * fgmipn(ji,jj))                         & ! Pn messy feeding remin., C
2959                 - (xthetarem * xphi * fgmidc(ji,jj))                                    & ! D  messy feeding remin., C
2960                 - (xthetarem * xthetapn * xphi * fgmepn(ji,jj))                         & ! Pn messy feeding remin., C
2961                 - (xthetarem * xthetapd * xphi * fgmepd(ji,jj))                         & ! Pd messy feeding remin., C
2962                 - (xthetarem * xthetazmi * xphi * fgmezmi(ji,jj))                       & ! Zi messy feeding remin., C
2963                 - (xthetarem * xphi * fgmedc(ji,jj))                                    & ! D  messy feeding remin., C
2964                 - (xthetarem * fmiresp(ji,jj))                                          & ! microzoo respiration, C
2965                 - (xthetarem * fmeresp(ji,jj))                                          & ! mesozoo  respiration, C
2966                 - (xthetarem * fddc(ji,jj))                                             & ! slow detritus remin., C
2967                 - (xthetarem * freminc(ji,jj))                                          & ! fast detritus remin., C
2968                 - (xthetarem * xthetapn * fdpn2(ji,jj))                                 & ! Pn  losses, C
2969                 - (xthetarem * xthetapd * fdpd2(ji,jj))                                 & ! Pd  losses, C
2970                 - (xthetarem * xthetazmi * fdzmi2(ji,jj))                               & ! Zmi losses, C
2971                 - (xthetarem * xthetazme * fdzme2(ji,jj))                                 ! Zme losses, C
2972               !! 
2973               !! benthic remineralisation
2974               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2975                  fo2_ccons(ji,jj) = fo2_ccons(ji,jj) - (xthetarem * f_benout_c(ji,jj) / fse3t(ji,jj,jk))
2976               endif
2977               fo2_cons(ji,jj) = fo2_ncons(ji,jj) + fo2_ccons(ji,jj)
2978               !!
2979               !! is this a suboxic zone?
2980               if (zoxy(ji,jj).lt.xo2min) then  ! deficient O2; production fluxes only
2981                  btra(ji,jj,jpoxy) = b0 * ( &
2982                    fo2_prod(ji,jj) )
2983                  foxy_prod(ji,jj) = foxy_prod(ji,jj) + ( fse3t(ji,jj,jk) * fo2_prod(ji,jj) )
2984                  foxy_anox(ji,jj) = foxy_anox(ji,jj) + ( fse3t(ji,jj,jk) * fo2_cons(ji,jj) )
2985               else                      ! sufficient O2; production + consumption fluxes
2986                  btra(ji,jj,jpoxy) = b0 * ( &
2987                    fo2_prod(ji,jj) + fo2_cons(ji,jj) )
2988                  foxy_prod(ji,jj) = foxy_prod(ji,jj) + ( fse3t(ji,jj,jk) * fo2_prod(ji,jj) )
2989                  foxy_cons(ji,jj) = foxy_cons(ji,jj) + ( fse3t(ji,jj,jk) * fo2_cons(ji,jj) )
2990               endif
2991               !!
2992               !! air-sea fluxes (if this is the surface box)
2993               if (jk.eq.1) then
2994                  !!
2995                  !! CO2 flux
2996                  btra(ji,jj,jpdic) = btra(ji,jj,jpdic) + (b0 * f_co2flux(ji,jj))
2997                  !!
2998                  !! O2 flux (mol/m3/s -> mmol/m3/d)
2999                  btra(ji,jj,jpoxy) = btra(ji,jj,jpoxy) + (b0 * f_o2flux(ji,jj))
3000               endif
3001# endif
3002
3003# if defined key_debug_medusa
3004               !! report state variable fluxes (not including fast-sinking detritus)
3005               if (idf.eq.1.AND.idfval.eq.1) then
3006                  IF (lwp) write (numout,*) '------------------------------'
3007                  IF (lwp) write (numout,*) 'btra(ji,jj,jpchn)(',jk,')  = ', btra(ji,jj,jpchn)
3008                  IF (lwp) write (numout,*) 'btra(ji,jj,jpchd)(',jk,')  = ', btra(ji,jj,jpchd)
3009                  IF (lwp) write (numout,*) 'btra(ji,jj,jpphn)(',jk,')  = ', btra(ji,jj,jpphn)
3010                  IF (lwp) write (numout,*) 'btra(ji,jj,jpphd)(',jk,')  = ', btra(ji,jj,jpphd)
3011                  IF (lwp) write (numout,*) 'btra(ji,jj,jppds)(',jk,')  = ', btra(ji,jj,jppds)
3012                  IF (lwp) write (numout,*) 'btra(ji,jj,jpzmi)(',jk,')  = ', btra(ji,jj,jpzmi)
3013                  IF (lwp) write (numout,*) 'btra(ji,jj,jpzme)(',jk,')  = ', btra(ji,jj,jpzme)
3014                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdet)(',jk,')  = ', btra(ji,jj,jpdet)
3015                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdin)(',jk,')  = ', btra(ji,jj,jpdin)
3016                  IF (lwp) write (numout,*) 'btra(ji,jj,jpsil)(',jk,')  = ', btra(ji,jj,jpsil)
3017                  IF (lwp) write (numout,*) 'btra(ji,jj,jpfer)(',jk,')  = ', btra(ji,jj,jpfer)
3018#  if defined key_roam
3019                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdtc)(',jk,')  = ', btra(ji,jj,jpdtc)
3020                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdic)(',jk,')  = ', btra(ji,jj,jpdic)
3021                  IF (lwp) write (numout,*) 'btra(ji,jj,jpalk)(',jk,')  = ', btra(ji,jj,jpalk)
3022                  IF (lwp) write (numout,*) 'btra(ji,jj,jpoxy)(',jk,')  = ', btra(ji,jj,jpoxy)
3023#  endif
3024               endif
3025# endif
3026
3027               !!----------------------------------------------------------------------
3028               !! Integrate calculated fluxes for mass balance
3029               !!----------------------------------------------------------------------
3030               !!
3031               !! === nitrogen ===
3032               fflx_n(ji,jj)  = fflx_n(ji,jj)  + &
3033                  fse3t(ji,jj,jk) * ( btra(ji,jj,jpphn) + btra(ji,jj,jpphd) + btra(ji,jj,jpzmi) + btra(ji,jj,jpzme) + btra(ji,jj,jpdet) + btra(ji,jj,jpdin) )
3034               !! === silicon ===
3035               fflx_si(ji,jj) = fflx_si(ji,jj) + &
3036                  fse3t(ji,jj,jk) * ( btra(ji,jj,jppds) + btra(ji,jj,jpsil) )
3037               !! === iron ===
3038               fflx_fe(ji,jj) = fflx_fe(ji,jj) + &
3039                  fse3t(ji,jj,jk) * ( ( xrfn * ( btra(ji,jj,jpphn) + btra(ji,jj,jpphd) + btra(ji,jj,jpzmi) + btra(ji,jj,jpzme) + btra(ji,jj,jpdet)) ) + btra(ji,jj,jpfer) )
3040# if defined key_roam
3041               !! === carbon ===
3042               fflx_c(ji,jj)  = fflx_c(ji,jj)  + &
3043                  fse3t(ji,jj,jk) * ( (xthetapn * btra(ji,jj,jpphn)) + (xthetapd * btra(ji,jj,jpphd)) + &
3044                  (xthetazmi * btra(ji,jj,jpzmi)) + (xthetazme * btra(ji,jj,jpzme)) + btra(ji,jj,jpdtc) + btra(ji,jj,jpdic) )
3045               !! === alkalinity ===
3046               fflx_a(ji,jj)  = fflx_a(ji,jj)  + &
3047                  fse3t(ji,jj,jk) * ( btra(ji,jj,jpalk) )
3048               !! === oxygen ===
3049               fflx_o2(ji,jj) = fflx_o2(ji,jj) + &
3050                  fse3t(ji,jj,jk) * ( btra(ji,jj,jpoxy) )
3051# endif
3052
3053               !!----------------------------------------------------------------------
3054               !! Apply calculated tracer fluxes
3055               !!----------------------------------------------------------------------
3056               !!
3057               !! units: [unit of tracer] per second (fluxes are calculated above per day)
3058               !!
3059               ibio_switch = 1
3060# if defined key_gulf_finland
3061               !! AXY (17/05/13): fudge in a Gulf of Finland correction; uses longitude-
3062               !!                 latitude range to establish if this is a Gulf of Finland
3063               !!                 grid cell; if so, then BGC fluxes are ignored (though
3064               !!                 still calculated); for reference, this is meant to be a
3065               !!                 temporary fix to see if all of my problems can be done
3066               !!                 away with if I switch off BGC fluxes in the Gulf of
3067               !!                 Finland, which currently appears the source of trouble
3068               if ( glamt(ji,jj).gt.24.7 .and. glamt(ji,jj).lt.27.8 .and. &
3069                  &   gphit(ji,jj).gt.59.2 .and. gphit(ji,jj).lt.60.2 ) then
3070                  ibio_switch = 0
3071               endif
3072# endif               
3073               if (ibio_switch.eq.1) then
3074                  tra(ji,jj,jk,jpchn) = tra(ji,jj,jk,jpchn) + (btra(ji,jj,jpchn) / 86400.)
3075                  tra(ji,jj,jk,jpchd) = tra(ji,jj,jk,jpchd) + (btra(ji,jj,jpchd) / 86400.)
3076                  tra(ji,jj,jk,jpphn) = tra(ji,jj,jk,jpphn) + (btra(ji,jj,jpphn) / 86400.)
3077                  tra(ji,jj,jk,jpphd) = tra(ji,jj,jk,jpphd) + (btra(ji,jj,jpphd) / 86400.)
3078                  tra(ji,jj,jk,jppds) = tra(ji,jj,jk,jppds) + (btra(ji,jj,jppds) / 86400.)
3079                  tra(ji,jj,jk,jpzmi) = tra(ji,jj,jk,jpzmi) + (btra(ji,jj,jpzmi) / 86400.)
3080                  tra(ji,jj,jk,jpzme) = tra(ji,jj,jk,jpzme) + (btra(ji,jj,jpzme) / 86400.)
3081                  tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + (btra(ji,jj,jpdet) / 86400.)
3082                  tra(ji,jj,jk,jpdin) = tra(ji,jj,jk,jpdin) + (btra(ji,jj,jpdin) / 86400.)
3083                  tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) + (btra(ji,jj,jpsil) / 86400.)
3084                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + (btra(ji,jj,jpfer) / 86400.)
3085# if defined key_roam
3086                  tra(ji,jj,jk,jpdtc) = tra(ji,jj,jk,jpdtc) + (btra(ji,jj,jpdtc) / 86400.)
3087                  tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) + (btra(ji,jj,jpdic) / 86400.)
3088                  tra(ji,jj,jk,jpalk) = tra(ji,jj,jk,jpalk) + (btra(ji,jj,jpalk) / 86400.)
3089                  tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) + (btra(ji,jj,jpoxy) / 86400.)
3090# endif
3091               endif               
3092
3093               !! AXY (18/11/16): CMIP6 diagnostics
3094               IF( med_diag%FBDDTALK%dgsave )  THEN
3095                  fbddtalk(ji,jj)  =  fbddtalk(ji,jj)  + (btra(ji,jj,jpalk) * fse3t(ji,jj,jk))
3096               ENDIF
3097               IF( med_diag%FBDDTDIC%dgsave )  THEN
3098                  fbddtdic(ji,jj)  =  fbddtdic(ji,jj)  + (btra(ji,jj,jpdic) * fse3t(ji,jj,jk))
3099               ENDIF
3100               IF( med_diag%FBDDTDIFE%dgsave ) THEN
3101                  fbddtdife(ji,jj) =  fbddtdife(ji,jj) + (btra(ji,jj,jpfer) * fse3t(ji,jj,jk))
3102               ENDIF
3103               IF( med_diag%FBDDTDIN%dgsave )  THEN
3104                  fbddtdin(ji,jj)  =  fbddtdin(ji,jj)  + (btra(ji,jj,jpdin) * fse3t(ji,jj,jk))
3105               ENDIF
3106               IF( med_diag%FBDDTDISI%dgsave ) THEN
3107                  fbddtdisi(ji,jj) =  fbddtdisi(ji,jj) + (btra(ji,jj,jpsil) * fse3t(ji,jj,jk))
3108               ENDIF
3109          !!
3110               IF( med_diag%BDDTALK3%dgsave )  THEN
3111                  bddtalk3(ji,jj,jk)  =  btra(ji,jj,jpalk)
3112               ENDIF
3113               IF( med_diag%BDDTDIC3%dgsave )  THEN
3114                  bddtdic3(ji,jj,jk)  =  btra(ji,jj,jpdic)
3115               ENDIF
3116               IF( med_diag%BDDTDIFE3%dgsave ) THEN
3117                  bddtdife3(ji,jj,jk) =  btra(ji,jj,jpfer)
3118               ENDIF
3119               IF( med_diag%BDDTDIN3%dgsave )  THEN
3120                  bddtdin3(ji,jj,jk)  =  btra(ji,jj,jpdin)
3121               ENDIF
3122               IF( med_diag%BDDTDISI3%dgsave ) THEN
3123                  bddtdisi3(ji,jj,jk) =  btra(ji,jj,jpsil)
3124               ENDIF
3125
3126#   if defined key_debug_medusa
3127               IF (lwp) write (numout,*) '------'
3128               IF (lwp) write (numout,*) 'trc_bio_medusa: end all calculations'
3129               IF (lwp) write (numout,*) 'trc_bio_medusa: now outputs'
3130                     CALL flush(numout)
3131#   endif
3132
3133# if defined key_axy_nancheck
3134               !!----------------------------------------------------------------------
3135               !! Check calculated tracer fluxes
3136               !!----------------------------------------------------------------------
3137               !!
3138               DO jn = 1,jptra
3139                  fq0 = btra(ji,jj,jn)
3140                  !! AXY (30/01/14): "isnan" problem on HECTOR
3141                  !! if (fq0 /= fq0 ) then
3142                  if ( ieee_is_nan( fq0 ) ) then
3143                     !! there's a NaN here
3144                     if (lwp) write(numout,*) 'NAN detected in btra(ji,jj,', ji, ',', &
3145                     & jj, ',', jk, ',', jn, ') at time', kt
3146           CALL ctl_stop( 'trcbio_medusa, NAN in btra field' )
3147                  endif
3148               ENDDO
3149               DO jn = 1,jptra
3150                  fq0 = tra(ji,jj,jk,jn)
3151                  !! AXY (30/01/14): "isnan" problem on HECTOR
3152                  !! if (fq0 /= fq0 ) then
3153                  if ( ieee_is_nan( fq0 ) ) then
3154                     !! there's a NaN here
3155                     if (lwp) write(numout,*) 'NAN detected in tra(', ji, ',', &
3156                     & jj, ',', jk, ',', jn, ') at time', kt
3157              CALL ctl_stop( 'trcbio_medusa, NAN in tra field' )
3158                  endif
3159               ENDDO
3160               CALL flush(numout)
3161# endif
3162
3163               !!----------------------------------------------------------------------
3164               !! Check model conservation
3165               !! these terms merely sum up the tendency terms of the relevant
3166               !! state variables, which should sum to zero; the iron cycle is
3167               !! complicated by fluxes that add (aeolian deposition and seafloor
3168               !! remineralisation) and remove (scavenging) dissolved iron from
3169               !! the model (i.e. the sum of iron fluxes is unlikely to be zero)
3170               !!----------------------------------------------------------------------
3171               !!
3172               !! fnit0 = btra(ji,jj,jpphn) + btra(ji,jj,jpphd) + btra(ji,jj,jpzmi) + btra(ji,jj,jpzme) + btra(ji,jj,jpdet) + btra(ji,jj,jpdin)  ! + ftempn(ji,jj)
3173               !! fsil0 = btra(ji,jj,jppds) + btra(ji,jj,jpsil)                              ! + ftempsi(ji,jj)
3174               !! ffer0 = (xrfn * fnit0) + btra(ji,jj,jpfer)
3175# if defined key_roam
3176               !! fcar0 = 0.
3177               !! falk0 = 0.
3178               !! foxy0 = 0.
3179# endif
3180               !!
3181               !! if (kt/240*240.eq.kt) then
3182               !!    if (ji.eq.2.and.jj.eq.2.and.jk.eq.1) then
3183               !!       IF (lwp) write (*,*) '*******!MEDUSA Conservation!*******',kt
3184# if defined key_roam
3185               !!       IF (lwp) write (*,*) fnit0,fsil0,ffer0,fcar0,falk0,foxy0
3186# else
3187               !!       IF (lwp) write (*,*) fnit0,fsil0,ffer0
3188# endif
3189               !!    endif
3190               !! endif     
3191
3192# if defined key_trc_diabio
3193               !!======================================================================
3194               !! LOCAL GRID CELL DIAGNOSTICS
3195               !!======================================================================
3196               !!
3197               !!----------------------------------------------------------------------
3198               !! Full diagnostics key_trc_diabio:
3199               !! LOBSTER and PISCES support full diagnistics option key_trc_diabio   
3200               !! which gives an option of FULL output of biological sourses and sinks.
3201               !! I cannot see any reason for doing this. If needed, it can be done
3202               !! as shown below.
3203               !!----------------------------------------------------------------------
3204               !!
3205               IF(lwp) WRITE(numout,*) ' MEDUSA does not support key_trc_diabio'
3206               !!               trbio(ji,jj,jk, 1) = fprn(ji,jj)
3207# endif
3208
3209               IF( lk_iomput  .AND.  .NOT.  ln_diatrc  ) THEN
3210         !!----------------------------------------------------------------------
3211         !! Add in XML diagnostics stuff
3212         !!----------------------------------------------------------------------
3213         !!
3214         !! ** 2D diagnostics
3215#   if defined key_debug_medusa
3216                  IF (lwp) write (numout,*) 'trc_bio_medusa: diag in ij-jj-jk loop'
3217                  CALL flush(numout)
3218#   endif
3219                  IF ( med_diag%PRN%dgsave ) THEN
3220                      fprn2d(ji,jj) = fprn2d(ji,jj) + (fprn(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3221                  ENDIF
3222                  IF ( med_diag%MPN%dgsave ) THEN
3223                      fdpn2d(ji,jj) = fdpn2d(ji,jj) + (fdpn(ji,jj)         * fse3t(ji,jj,jk))
3224                  ENDIF
3225                  IF ( med_diag%PRD%dgsave ) THEN
3226                      fprd2d(ji,jj) = fprd2d(ji,jj) + (fprd(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))
3227                  ENDIF
3228                  IF( med_diag%MPD%dgsave ) THEN
3229                      fdpd2d(ji,jj) = fdpd2d(ji,jj) + (fdpd(ji,jj)         * fse3t(ji,jj,jk)) 
3230                  ENDIF
3231                  !  IF( med_diag%DSED%dgsave ) THEN
3232                  !      CALL iom_put( "DSED"  , ftot_n )
3233                  !  ENDIF
3234                  IF( med_diag%OPAL%dgsave ) THEN
3235                      fprds2d(ji,jj) = fprds2d(ji,jj) + (fprds(ji,jj) * zpds(ji,jj) * fse3t(ji,jj,jk)) 
3236                  ENDIF
3237                  IF( med_diag%OPALDISS%dgsave ) THEN
3238                      fsdiss2d(ji,jj) = fsdiss2d(ji,jj) + (fsdiss(ji,jj)  * fse3t(ji,jj,jk)) 
3239                  ENDIF
3240                  IF( med_diag%GMIPn%dgsave ) THEN
3241                      fgmipn2d(ji,jj) = fgmipn2d(ji,jj) + (fgmipn(ji,jj)  * fse3t(ji,jj,jk)) 
3242                  ENDIF
3243                  IF( med_diag%GMID%dgsave ) THEN
3244                      fgmid2d(ji,jj) = fgmid2d(ji,jj) + (fgmid(ji,jj)   * fse3t(ji,jj,jk)) 
3245                  ENDIF
3246                  IF( med_diag%MZMI%dgsave ) THEN
3247                      fdzmi2d(ji,jj) = fdzmi2d(ji,jj) + (fdzmi(ji,jj)   * fse3t(ji,jj,jk)) 
3248                  ENDIF
3249                  IF( med_diag%GMEPN%dgsave ) THEN
3250                      fgmepn2d(ji,jj) = fgmepn2d(ji,jj) + (fgmepn(ji,jj)  * fse3t(ji,jj,jk))
3251                  ENDIF
3252                  IF( med_diag%GMEPD%dgsave ) THEN
3253                      fgmepd2d(ji,jj) = fgmepd2d(ji,jj) + (fgmepd(ji,jj)  * fse3t(ji,jj,jk)) 
3254                  ENDIF
3255                  IF( med_diag%GMEZMI%dgsave ) THEN
3256                      fgmezmi2d(ji,jj) = fgmezmi2d(ji,jj) + (fgmezmi(ji,jj) * fse3t(ji,jj,jk)) 
3257                  ENDIF
3258                  IF( med_diag%GMED%dgsave ) THEN
3259                      fgmed2d(ji,jj) = fgmed2d(ji,jj) + (fgmed(ji,jj)   * fse3t(ji,jj,jk)) 
3260                  ENDIF
3261                  IF( med_diag%MZME%dgsave ) THEN
3262                      fdzme2d(ji,jj) = fdzme2d(ji,jj) + (fdzme(ji,jj)   * fse3t(ji,jj,jk)) 
3263                  ENDIF
3264                  !  IF( med_diag%DEXP%dgsave ) THEN
3265                  !      CALL iom_put( "DEXP"  , ftot_n )
3266                  !  ENDIF
3267                  IF( med_diag%DETN%dgsave ) THEN
3268                      fslown2d(ji,jj) = fslown2d(ji,jj) + (fslown(ji,jj)  * fse3t(ji,jj,jk)) 
3269                  ENDIF
3270                  IF( med_diag%MDET%dgsave ) THEN
3271                      fdd2d(ji,jj) = fdd2d(ji,jj) + (fdd(ji,jj)     * fse3t(ji,jj,jk)) 
3272                  ENDIF
3273                  IF( med_diag%AEOLIAN%dgsave ) THEN
3274                      ffetop2d(ji,jj) = ffetop2d(ji,jj) + (ffetop(ji,jj)  * fse3t(ji,jj,jk)) 
3275                  ENDIF
3276                  IF( med_diag%BENTHIC%dgsave ) THEN
3277                      ffebot2d(ji,jj) = ffebot2d(ji,jj) + (ffebot(ji,jj)  * fse3t(ji,jj,jk)) 
3278                  ENDIF
3279                  IF( med_diag%SCAVENGE%dgsave ) THEN
3280                      ffescav2d(ji,jj) = ffescav2d(ji,jj) + (ffescav(ji,jj) * fse3t(ji,jj,jk)) 
3281                  ENDIF
3282                  IF( med_diag%PN_JLIM%dgsave ) THEN
3283                      ! fjln2d(ji,jj) = fjln2d(ji,jj) + (fjln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk))
3284                      fjln2d(ji,jj) = fjln2d(ji,jj) + (fjlim_pn(ji,jj) * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3285                  ENDIF
3286                  IF( med_diag%PN_NLIM%dgsave ) THEN
3287                      fnln2d(ji,jj) = fnln2d(ji,jj) + (fnln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3288                  ENDIF
3289                  IF( med_diag%PN_FELIM%dgsave ) THEN
3290                      ffln2d(ji,jj) = ffln2d(ji,jj) + (ffln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3291                  ENDIF
3292                  IF( med_diag%PD_JLIM%dgsave ) THEN
3293                      ! fjld2d(ji,jj) = fjld2d(ji,jj) + (fjld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))
3294                      fjld2d(ji,jj) = fjld2d(ji,jj) + (fjlim_pd(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3295                  ENDIF
3296                  IF( med_diag%PD_NLIM%dgsave ) THEN
3297                      fnld2d(ji,jj) = fnld2d(ji,jj) + (fnld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3298                  ENDIF
3299                  IF( med_diag%PD_FELIM%dgsave ) THEN
3300                      ffld2d(ji,jj) = ffld2d(ji,jj) + (ffld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3301                  ENDIF
3302                  IF( med_diag%PD_SILIM%dgsave ) THEN
3303                      fsld2d2(ji,jj) = fsld2d2(ji,jj) + (fsld2(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3304                  ENDIF
3305                  IF( med_diag%PDSILIM2%dgsave ) THEN
3306                      fsld2d(ji,jj) = fsld2d(ji,jj) + (fsld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))
3307                  ENDIF
3308                  !!
3309                  IF( med_diag%TOTREG_N%dgsave ) THEN
3310                      fregen2d(ji,jj) = fregen2d(ji,jj) + fregen(ji,jj)
3311                  ENDIF
3312                  IF( med_diag%TOTRG_SI%dgsave ) THEN
3313                      fregensi2d(ji,jj) = fregensi2d(ji,jj) + fregensi(ji,jj)
3314                  ENDIF
3315                  !!
3316                  IF( med_diag%FASTN%dgsave ) THEN
3317                      ftempn2d(ji,jj) = ftempn2d(ji,jj) + (ftempn(ji,jj)  * fse3t(ji,jj,jk))
3318                  ENDIF
3319                  IF( med_diag%FASTSI%dgsave ) THEN
3320                      ftempsi2d(ji,jj) = ftempsi2d(ji,jj) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))
3321                  ENDIF
3322                  IF( med_diag%FASTFE%dgsave ) THEN
3323                      ftempfe2d(ji,jj) =ftempfe2d(ji,jj)  + (ftempfe(ji,jj) * fse3t(ji,jj,jk)) 
3324                  ENDIF
3325                  IF( med_diag%FASTC%dgsave ) THEN
3326                      ftempc2d(ji,jj) = ftempc2d(ji,jj) + (ftempc(ji,jj)  * fse3t(ji,jj,jk))
3327                  ENDIF
3328                  IF( med_diag%FASTCA%dgsave ) THEN
3329                      ftempca2d(ji,jj) = ftempca2d(ji,jj) + (ftempca(ji,jj) * fse3t(ji,jj,jk))
3330                  ENDIF
3331                  !!
3332                  IF( med_diag%REMINN%dgsave ) THEN
3333                      freminn2d(ji,jj) = freminn2d(ji,jj) + (freminn(ji,jj)  * fse3t(ji,jj,jk))
3334                  ENDIF
3335                  IF( med_diag%REMINSI%dgsave ) THEN
3336                      freminsi2d(ji,jj) = freminsi2d(ji,jj) + (freminsi(ji,jj) * fse3t(ji,jj,jk))
3337                  ENDIF
3338                  IF( med_diag%REMINFE%dgsave ) THEN
3339                      freminfe2d(ji,jj)= freminfe2d(ji,jj) + (freminfe(ji,jj) * fse3t(ji,jj,jk)) 
3340                  ENDIF
3341                  IF( med_diag%REMINC%dgsave ) THEN
3342                      freminc2d(ji,jj) = freminc2d(ji,jj) + (freminc(ji,jj)  * fse3t(ji,jj,jk)) 
3343                  ENDIF
3344                  IF( med_diag%REMINCA%dgsave ) THEN
3345                      freminca2d(ji,jj) = freminca2d(ji,jj) + (freminca(ji,jj) * fse3t(ji,jj,jk)) 
3346                  ENDIF
3347                  !!
3348# if defined key_roam
3349                  !!
3350                  !! AXY (09/11/16): CMIP6 diagnostics
3351                  IF( med_diag%FD_NIT3%dgsave ) THEN
3352                     fd_nit3(ji,jj,jk) = ffastn(ji,jj)
3353                  ENDIF
3354                  IF( med_diag%FD_SIL3%dgsave ) THEN
3355                     fd_sil3(ji,jj,jk) = ffastsi(ji,jj)
3356                  ENDIF
3357                  IF( med_diag%FD_CAR3%dgsave ) THEN
3358                     fd_car3(ji,jj,jk) = ffastc(ji,jj)
3359                  ENDIF
3360                  IF( med_diag%FD_CAL3%dgsave ) THEN
3361                     fd_cal3(ji,jj,jk) = ffastca(ji,jj)
3362                  ENDIF
3363                  !!
3364                  IF (jk.eq.i0100) THEN
3365                     IF( med_diag%RR_0100%dgsave ) THEN
3366                        ffastca2d(ji,jj) =   &
3367                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)
3368                     ENDIF                     
3369                  ELSE IF (jk.eq.i0500) THEN
3370                     IF( med_diag%RR_0500%dgsave ) THEN
3371                        ffastca2d(ji,jj) =   &
3372                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)
3373                     ENDIF                       
3374                  ELSE IF (jk.eq.i1000) THEN
3375                     IF( med_diag%RR_1000%dgsave ) THEN
3376                        ffastca2d(ji,jj) =   &
3377                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)
3378                     ENDIF
3379                  ELSE IF (jk.eq.mbathy(ji,jj)) THEN
3380                     IF( med_diag%IBEN_N%dgsave ) THEN
3381                        iben_n2d(ji,jj) = f_sbenin_n(ji,jj)  + f_fbenin_n(ji,jj)
3382                     ENDIF
3383                     IF( med_diag%IBEN_FE%dgsave ) THEN
3384                        iben_fe2d(ji,jj) = f_sbenin_fe(ji,jj) + f_fbenin_fe(ji,jj)
3385                     ENDIF
3386                     IF( med_diag%IBEN_C%dgsave ) THEN
3387                        iben_c2d(ji,jj) = f_sbenin_c(ji,jj)  + f_fbenin_c(ji,jj)
3388                     ENDIF
3389                     IF( med_diag%IBEN_SI%dgsave ) THEN
3390                        iben_si2d(ji,jj) = f_fbenin_si(ji,jj)
3391                     ENDIF
3392                     IF( med_diag%IBEN_CA%dgsave ) THEN
3393                        iben_ca2d(ji,jj) = f_fbenin_ca(ji,jj)
3394                     ENDIF
3395                     IF( med_diag%OBEN_N%dgsave ) THEN
3396                        oben_n2d(ji,jj) = f_benout_n(ji,jj)
3397                     ENDIF
3398                     IF( med_diag%OBEN_FE%dgsave ) THEN
3399                        oben_fe2d(ji,jj) = f_benout_fe(ji,jj)
3400                     ENDIF
3401                     IF( med_diag%OBEN_C%dgsave ) THEN
3402                        oben_c2d(ji,jj) = f_benout_c(ji,jj)
3403                     ENDIF
3404                     IF( med_diag%OBEN_SI%dgsave ) THEN
3405                        oben_si2d(ji,jj) = f_benout_si(ji,jj)
3406                     ENDIF
3407                     IF( med_diag%OBEN_CA%dgsave ) THEN
3408                        oben_ca2d(ji,jj) = f_benout_ca(ji,jj)
3409                     ENDIF
3410                     IF( med_diag%SFR_OCAL%dgsave ) THEN
3411                        sfr_ocal2d(ji,jj) = f3_omcal(ji,jj,jk)
3412                     ENDIF
3413                     IF( med_diag%SFR_OARG%dgsave ) THEN
3414                        sfr_oarg2d(ji,jj) =  f3_omarg(ji,jj,jk)
3415                     ENDIF
3416                     IF( med_diag%LYSO_CA%dgsave ) THEN
3417                        lyso_ca2d(ji,jj) = f_benout_lyso_ca(ji,jj)
3418                     ENDIF
3419                  ENDIF
3420                  !! end bathy-1 diags
3421                  !!
3422                  IF( med_diag%RIV_N%dgsave ) THEN
3423                     rivn2d(ji,jj) = rivn2d(ji,jj) +  (f_riv_loc_n(ji,jj) * fse3t(ji,jj,jk))
3424                  ENDIF
3425                  IF( med_diag%RIV_SI%dgsave ) THEN
3426                     rivsi2d(ji,jj) = rivsi2d(ji,jj) +  (f_riv_loc_si(ji,jj) * fse3t(ji,jj,jk))
3427                  ENDIF
3428                  IF( med_diag%RIV_C%dgsave ) THEN
3429                     rivc2d(ji,jj) = rivc2d(ji,jj) +  (f_riv_loc_c(ji,jj) * fse3t(ji,jj,jk))
3430                  ENDIF
3431                  IF( med_diag%RIV_ALK%dgsave ) THEN
3432                     rivalk2d(ji,jj) = rivalk2d(ji,jj) +  (f_riv_loc_alk(ji,jj) * fse3t(ji,jj,jk))
3433                  ENDIF
3434                  IF( med_diag%DETC%dgsave ) THEN
3435                     fslowc2d(ji,jj) = fslowc2d(ji,jj) + (fslowc(ji,jj)  * fse3t(ji,jj,jk))   
3436                  ENDIF
3437                  !!
3438                  !!             
3439                  !!
3440                  IF( med_diag%PN_LLOSS%dgsave ) THEN
3441                     fdpn22d(ji,jj) = fdpn22d(ji,jj) + (fdpn2(ji,jj)  * fse3t(ji,jj,jk))
3442                  ENDIF
3443                  IF( med_diag%PD_LLOSS%dgsave ) THEN
3444                     fdpd22d(ji,jj) = fdpd22d(ji,jj) + (fdpd2(ji,jj)  * fse3t(ji,jj,jk))
3445                  ENDIF
3446                  IF( med_diag%ZI_LLOSS%dgsave ) THEN
3447                     fdzmi22d(ji,jj) = fdzmi22d(ji,jj) + (fdzmi2(ji,jj) * fse3t(ji,jj,jk))
3448                  ENDIF
3449                  IF( med_diag%ZE_LLOSS%dgsave ) THEN
3450                     fdzme22d(ji,jj) = fdzme22d(ji,jj) + (fdzme2(ji,jj) * fse3t(ji,jj,jk))
3451                  ENDIF
3452                  IF( med_diag%ZI_MES_N%dgsave ) THEN
3453                     zimesn2d(ji,jj) = zimesn2d(ji,jj) +  &
3454                     (xphi * (fgmipn(ji,jj) + fgmid(ji,jj)) * fse3t(ji,jj,jk))
3455                  ENDIF
3456                  IF( med_diag%ZI_MES_D%dgsave ) THEN
3457                     zimesd2d(ji,jj) = zimesd2d(ji,jj) + & 
3458                     ((1. - xbetan) * finmi(ji,jj) * fse3t(ji,jj,jk))
3459                  ENDIF
3460                  IF( med_diag%ZI_MES_C%dgsave ) THEN
3461                     zimesc2d(ji,jj) = zimesc2d(ji,jj) + &
3462                     (xphi * ((xthetapn * fgmipn(ji,jj)) + fgmidc(ji,jj)) * fse3t(ji,jj,jk))
3463                  ENDIF
3464                  IF( med_diag%ZI_MESDC%dgsave ) THEN
3465                     zimesdc2d(ji,jj) = zimesdc2d(ji,jj) + &
3466                     ((1. - xbetac) * ficmi(ji,jj) * fse3t(ji,jj,jk))
3467                  ENDIF
3468                  IF( med_diag%ZI_EXCR%dgsave ) THEN
3469                     ziexcr2d(ji,jj) = ziexcr2d(ji,jj) +  (fmiexcr(ji,jj) * fse3t(ji,jj,jk))
3470                  ENDIF
3471                  IF( med_diag%ZI_RESP%dgsave ) THEN
3472                     ziresp2d(ji,jj) = ziresp2d(ji,jj) +  (fmiresp(ji,jj) * fse3t(ji,jj,jk))
3473                  ENDIF
3474                  IF( med_diag%ZI_GROW%dgsave ) THEN
3475                     zigrow2d(ji,jj) = zigrow2d(ji,jj) + (fmigrow(ji,jj) * fse3t(ji,jj,jk))
3476                  ENDIF
3477                  IF( med_diag%ZE_MES_N%dgsave ) THEN
3478                     zemesn2d(ji,jj) = zemesn2d(ji,jj) + &
3479                     (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj)) * fse3t(ji,jj,jk))
3480                  ENDIF
3481                  IF( med_diag%ZE_MES_D%dgsave ) THEN
3482                     zemesd2d(ji,jj) = zemesd2d(ji,jj) + &
3483                     ((1. - xbetan) * finme(ji,jj) * fse3t(ji,jj,jk))
3484                  ENDIF
3485                  IF( med_diag%ZE_MES_C%dgsave ) THEN
3486                     zemesc2d(ji,jj) = zemesc2d(ji,jj) +                         & 
3487                     (xphi * ((xthetapn * fgmepn(ji,jj)) + (xthetapd * fgmepd(ji,jj)) +  &
3488                     (xthetazmi * fgmezmi(ji,jj)) + fgmedc(ji,jj)) * fse3t(ji,jj,jk))
3489                  ENDIF
3490                  IF( med_diag%ZE_MESDC%dgsave ) THEN
3491                     zemesdc2d(ji,jj) = zemesdc2d(ji,jj) +  &
3492                     ((1. - xbetac) * ficme(ji,jj) * fse3t(ji,jj,jk))
3493                  ENDIF
3494                  IF( med_diag%ZE_EXCR%dgsave ) THEN
3495                     zeexcr2d(ji,jj) = zeexcr2d(ji,jj) + (fmeexcr(ji,jj) * fse3t(ji,jj,jk))
3496                  ENDIF
3497                  IF( med_diag%ZE_RESP%dgsave ) THEN
3498                     zeresp2d(ji,jj) = zeresp2d(ji,jj) + (fmeresp(ji,jj) * fse3t(ji,jj,jk))
3499                  ENDIF
3500                  IF( med_diag%ZE_GROW%dgsave ) THEN
3501                     zegrow2d(ji,jj) = zegrow2d(ji,jj) + (fmegrow(ji,jj) * fse3t(ji,jj,jk))
3502                  ENDIF
3503                  IF( med_diag%MDETC%dgsave ) THEN
3504                     mdetc2d(ji,jj) = mdetc2d(ji,jj) + (fddc(ji,jj) * fse3t(ji,jj,jk))
3505                  ENDIF
3506                  IF( med_diag%GMIDC%dgsave ) THEN
3507                     gmidc2d(ji,jj) = gmidc2d(ji,jj) + (fgmidc(ji,jj) * fse3t(ji,jj,jk))
3508                  ENDIF
3509                  IF( med_diag%GMEDC%dgsave ) THEN
3510                     gmedc2d(ji,jj) = gmedc2d(ji,jj) + (fgmedc(ji,jj)  * fse3t(ji,jj,jk))
3511                  ENDIF
3512                  !!
3513# endif                   
3514                  !!
3515                  !! ** 3D diagnostics
3516                  IF( med_diag%TPP3%dgsave ) THEN
3517                     tpp3d(ji,jj,jk) =  (fprn(ji,jj) * zphn(ji,jj)) + (fprd(ji,jj) * zphd(ji,jj))
3518                     !CALL iom_put( "TPP3"  , tpp3d )
3519                  ENDIF
3520                  IF( med_diag%TPPD3%dgsave ) THEN
3521                     tppd3(ji,jj,jk) =  (fprd(ji,jj) * zphd(ji,jj))
3522                  ENDIF
3523                 
3524                  IF( med_diag%REMIN3N%dgsave ) THEN
3525                     remin3dn(ji,jj,jk) = fregen(ji,jj) + (freminn(ji,jj) * fse3t(ji,jj,jk)) !! remineralisation
3526                     !CALL iom_put( "REMIN3N"  , remin3dn )
3527                  ENDIF
3528                  !! IF( med_diag%PH3%dgsave ) THEN
3529                  !!     CALL iom_put( "PH3"  , f3_pH )
3530                  !! ENDIF
3531                  !! IF( med_diag%OM_CAL3%dgsave ) THEN
3532                  !!     CALL iom_put( "OM_CAL3"  , f3_omcal )
3533                  !! ENDIF
3534        !!
3535        !! AXY (09/11/16): CMIP6 diagnostics
3536        IF ( med_diag%DCALC3%dgsave   ) THEN
3537                     dcalc3(ji,jj,jk) = freminca(ji,jj)
3538                  ENDIF
3539        IF ( med_diag%FEDISS3%dgsave  ) THEN
3540                     fediss3(ji,jj,jk) = ffetop(ji,jj)
3541                  ENDIF
3542        IF ( med_diag%FESCAV3%dgsave  ) THEN
3543                     fescav3(ji,jj,jk) = ffescav(ji,jj)
3544                  ENDIF
3545        IF ( med_diag%MIGRAZP3%dgsave ) THEN
3546                     migrazp3(ji,jj,jk) = fgmipn(ji,jj) * xthetapn
3547                  ENDIF
3548        IF ( med_diag%MIGRAZD3%dgsave ) THEN
3549                     migrazd3(ji,jj,jk) = fgmidc(ji,jj)
3550                  ENDIF
3551        IF ( med_diag%MEGRAZP3%dgsave ) THEN
3552                     megrazp3(ji,jj,jk) = (fgmepn(ji,jj) * xthetapn) + (fgmepd(ji,jj) * xthetapd)
3553                  ENDIF
3554        IF ( med_diag%MEGRAZD3%dgsave ) THEN
3555                     megrazd3(ji,jj,jk) = fgmedc(ji,jj)
3556                  ENDIF
3557        IF ( med_diag%MEGRAZZ3%dgsave ) THEN
3558                     megrazz3(ji,jj,jk) = (fgmezmi(ji,jj) * xthetazmi)
3559                  ENDIF
3560        IF ( med_diag%PBSI3%dgsave    ) THEN
3561                     pbsi3(ji,jj,jk)    = (fprds(ji,jj) * zpds(ji,jj))
3562                  ENDIF
3563        IF ( med_diag%PCAL3%dgsave    ) THEN
3564                     pcal3(ji,jj,jk)    = ftempca(ji,jj)
3565                  ENDIF
3566        IF ( med_diag%REMOC3%dgsave   ) THEN
3567                     remoc3(ji,jj,jk)   = freminc(ji,jj)
3568                  ENDIF
3569        IF ( med_diag%PNLIMJ3%dgsave  ) THEN
3570                     ! pnlimj3(ji,jj,jk)  = fjln(ji,jj)
3571                     pnlimj3(ji,jj,jk)  = fjlim_pn(ji,jj)
3572                  ENDIF
3573        IF ( med_diag%PNLIMN3%dgsave  ) THEN
3574                     pnlimn3(ji,jj,jk)  = fnln(ji,jj)
3575                  ENDIF
3576        IF ( med_diag%PNLIMFE3%dgsave ) THEN
3577                     pnlimfe3(ji,jj,jk) = ffln(ji,jj)
3578                  ENDIF
3579        IF ( med_diag%PDLIMJ3%dgsave  ) THEN
3580                     ! pdlimj3(ji,jj,jk)  = fjld(ji,jj)
3581                     pdlimj3(ji,jj,jk)  = fjlim_pd(ji,jj)
3582                  ENDIF
3583        IF ( med_diag%PDLIMN3%dgsave  ) THEN
3584                     pdlimn3(ji,jj,jk)  = fnld(ji,jj)
3585                  ENDIF
3586        IF ( med_diag%PDLIMFE3%dgsave ) THEN
3587                     pdlimfe3(ji,jj,jk) = ffld(ji,jj)
3588                  ENDIF
3589        IF ( med_diag%PDLIMSI3%dgsave ) THEN
3590                     pdlimsi3(ji,jj,jk) = fsld2(ji,jj)
3591                  ENDIF
3592                  !!
3593                  !! ** Without using iom_use
3594               ELSE IF( ln_diatrc ) THEN
3595#   if defined key_debug_medusa
3596                  IF (lwp) write (numout,*) 'trc_bio_medusa: diag in ij-jj-jk ln_diatrc'
3597                  CALL flush(numout)
3598#   endif
3599                  !!----------------------------------------------------------------------
3600                  !! Prepare 2D diagnostics
3601                  !!----------------------------------------------------------------------
3602                  !!
3603                  !! if ((kt / 240*240).eq.kt) then
3604                  !!    IF (lwp) write (*,*) '*******!MEDUSA DIAADD!*******',kt
3605                  !! endif     
3606                  trc2d(ji,jj,1)  =  ftot_n(ji,jj)                             !! nitrogen inventory
3607                  trc2d(ji,jj,2)  =  ftot_si(ji,jj)                            !! silicon  inventory
3608                  trc2d(ji,jj,3)  =  ftot_fe(ji,jj)                            !! iron     inventory
3609                  trc2d(ji,jj,4)  = trc2d(ji,jj,4)  + (fprn(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk))    !! non-diatom production
3610                  trc2d(ji,jj,5)  = trc2d(ji,jj,5)  + (fdpn(ji,jj)         * fse3t(ji,jj,jk))    !! non-diatom non-grazing losses
3611                  trc2d(ji,jj,6)  = trc2d(ji,jj,6)  + (fprd(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))    !! diatom production
3612                  trc2d(ji,jj,7)  = trc2d(ji,jj,7)  + (fdpd(ji,jj)         * fse3t(ji,jj,jk))    !! diatom non-grazing losses
3613                  !! diagnostic field  8 is (ostensibly) supplied by trcsed.F           
3614                  trc2d(ji,jj,9)  = trc2d(ji,jj,9)  + (fprds(ji,jj) * zpds(ji,jj) * fse3t(ji,jj,jk))    !! diatom silicon production
3615                  trc2d(ji,jj,10) = trc2d(ji,jj,10) + (fsdiss(ji,jj)  * fse3t(ji,jj,jk))         !! diatom silicon dissolution
3616                  trc2d(ji,jj,11) = trc2d(ji,jj,11) + (fgmipn(ji,jj)  * fse3t(ji,jj,jk))         !! microzoo grazing on non-diatoms
3617                  trc2d(ji,jj,12) = trc2d(ji,jj,12) + (fgmid(ji,jj)   * fse3t(ji,jj,jk))         !! microzoo grazing on detrital nitrogen
3618                  trc2d(ji,jj,13) = trc2d(ji,jj,13) + (fdzmi(ji,jj)   * fse3t(ji,jj,jk))         !! microzoo non-grazing losses
3619                  trc2d(ji,jj,14) = trc2d(ji,jj,14) + (fgmepn(ji,jj)  * fse3t(ji,jj,jk))         !! mesozoo  grazing on non-diatoms
3620                  trc2d(ji,jj,15) = trc2d(ji,jj,15) + (fgmepd(ji,jj)  * fse3t(ji,jj,jk))         !! mesozoo  grazing on diatoms
3621                  trc2d(ji,jj,16) = trc2d(ji,jj,16) + (fgmezmi(ji,jj) * fse3t(ji,jj,jk))         !! mesozoo  grazing on microzoo
3622                  trc2d(ji,jj,17) = trc2d(ji,jj,17) + (fgmed(ji,jj)   * fse3t(ji,jj,jk))         !! mesozoo  grazing on detrital nitrogen
3623                  trc2d(ji,jj,18) = trc2d(ji,jj,18) + (fdzme(ji,jj)   * fse3t(ji,jj,jk))         !! mesozoo  non-grazing losses
3624                  !! diagnostic field 19 is (ostensibly) supplied by trcexp.F
3625                  trc2d(ji,jj,20) = trc2d(ji,jj,20) + (fslown(ji,jj)  * fse3t(ji,jj,jk))         !! slow sinking detritus N production
3626                  trc2d(ji,jj,21) = trc2d(ji,jj,21) + (fdd(ji,jj)     * fse3t(ji,jj,jk))         !! detrital remineralisation
3627                  trc2d(ji,jj,22) = trc2d(ji,jj,22) + (ffetop(ji,jj)  * fse3t(ji,jj,jk))         !! aeolian  iron addition
3628                  trc2d(ji,jj,23) = trc2d(ji,jj,23) + (ffebot(ji,jj)  * fse3t(ji,jj,jk))         !! seafloor iron addition
3629                  trc2d(ji,jj,24) = trc2d(ji,jj,24) + (ffescav(ji,jj) * fse3t(ji,jj,jk))         !! "free" iron scavenging
3630                  trc2d(ji,jj,25) = trc2d(ji,jj,25) + (fjlim_pn(ji,jj) * zphn(ji,jj) * fse3t(ji,jj,jk)) !! non-diatom J  limitation term
3631                  trc2d(ji,jj,26) = trc2d(ji,jj,26) + (fnln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk))    !! non-diatom N  limitation term
3632                  trc2d(ji,jj,27) = trc2d(ji,jj,27) + (ffln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk))    !! non-diatom Fe limitation term
3633                  trc2d(ji,jj,28) = trc2d(ji,jj,28) + (fjlim_pd(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk)) !! diatom     J  limitation term
3634                  trc2d(ji,jj,29) = trc2d(ji,jj,29) + (fnld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))    !! diatom     N  limitation term
3635                  trc2d(ji,jj,30) = trc2d(ji,jj,30) + (ffld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))    !! diatom     Fe limitation term
3636                  trc2d(ji,jj,31) = trc2d(ji,jj,31) + (fsld2(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk))    !! diatom     Si limitation term
3637                  trc2d(ji,jj,32) = trc2d(ji,jj,32) + (fsld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))    !! diatom     Si uptake limitation term
3638                  if (jk.eq.i0100) trc2d(ji,jj,33) = fslownflux(ji,jj)         !! slow detritus flux at  100 m
3639                  if (jk.eq.i0200) trc2d(ji,jj,34) = fslownflux(ji,jj)         !! slow detritus flux at  200 m
3640                  if (jk.eq.i0500) trc2d(ji,jj,35) = fslownflux(ji,jj)         !! slow detritus flux at  500 m
3641                  if (jk.eq.i1000) trc2d(ji,jj,36) = fslownflux(ji,jj)         !! slow detritus flux at 1000 m
3642                  trc2d(ji,jj,37) = trc2d(ji,jj,37) + fregen(ji,jj)                   !! non-fast N  full column regeneration
3643                  trc2d(ji,jj,38) = trc2d(ji,jj,38) + fregensi(ji,jj)                 !! non-fast Si full column regeneration
3644                  if (jk.eq.i0100) trc2d(ji,jj,39) = trc2d(ji,jj,37)           !! non-fast N  regeneration to  100 m
3645                  if (jk.eq.i0200) trc2d(ji,jj,40) = trc2d(ji,jj,37)           !! non-fast N  regeneration to  200 m
3646                  if (jk.eq.i0500) trc2d(ji,jj,41) = trc2d(ji,jj,37)           !! non-fast N  regeneration to  500 m
3647                  if (jk.eq.i1000) trc2d(ji,jj,42) = trc2d(ji,jj,37)           !! non-fast N  regeneration to 1000 m
3648                  trc2d(ji,jj,43) = trc2d(ji,jj,43) + (ftempn(ji,jj)  * fse3t(ji,jj,jk))         !! fast sinking detritus N production
3649                  trc2d(ji,jj,44) = trc2d(ji,jj,44) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))         !! fast sinking detritus Si production
3650                  trc2d(ji,jj,45) = trc2d(ji,jj,45) + (ftempfe(ji,jj) * fse3t(ji,jj,jk))         !! fast sinking detritus Fe production
3651                  trc2d(ji,jj,46) = trc2d(ji,jj,46) + (ftempc(ji,jj)  * fse3t(ji,jj,jk))         !! fast sinking detritus C production
3652                  trc2d(ji,jj,47) = trc2d(ji,jj,47) + (ftempca(ji,jj) * fse3t(ji,jj,jk))         !! fast sinking detritus CaCO3 production
3653                  if (jk.eq.i0100) trc2d(ji,jj,48) = ffastn(ji,jj)             !! fast detritus N  flux at  100 m
3654                  if (jk.eq.i0200) trc2d(ji,jj,49) = ffastn(ji,jj)             !! fast detritus N  flux at  200 m
3655                  if (jk.eq.i0500) trc2d(ji,jj,50) = ffastn(ji,jj)             !! fast detritus N  flux at  500 m
3656                  if (jk.eq.i1000) trc2d(ji,jj,51) = ffastn(ji,jj)             !! fast detritus N  flux at 1000 m
3657                  if (jk.eq.i0100) trc2d(ji,jj,52) = fregenfast(ji,jj)         !! N  regeneration to  100 m
3658                  if (jk.eq.i0200) trc2d(ji,jj,53) = fregenfast(ji,jj)         !! N  regeneration to  200 m
3659                  if (jk.eq.i0500) trc2d(ji,jj,54) = fregenfast(ji,jj)         !! N  regeneration to  500 m
3660                  if (jk.eq.i1000) trc2d(ji,jj,55) = fregenfast(ji,jj)         !! N  regeneration to 1000 m
3661                  if (jk.eq.i0100) trc2d(ji,jj,56) = ffastsi(ji,jj)            !! fast detritus Si flux at  100 m
3662                  if (jk.eq.i0200) trc2d(ji,jj,57) = ffastsi(ji,jj)            !! fast detritus Si flux at  200 m
3663                  if (jk.eq.i0500) trc2d(ji,jj,58) = ffastsi(ji,jj)            !! fast detritus Si flux at  500 m
3664                  if (jk.eq.i1000) trc2d(ji,jj,59) = ffastsi(ji,jj)            !! fast detritus Si flux at 1000 m
3665                  if (jk.eq.i0100) trc2d(ji,jj,60) = fregenfastsi(ji,jj)       !! Si regeneration to  100 m
3666                  if (jk.eq.i0200) trc2d(ji,jj,61) = fregenfastsi(ji,jj)       !! Si regeneration to  200 m
3667                  if (jk.eq.i0500) trc2d(ji,jj,62) = fregenfastsi(ji,jj)       !! Si regeneration to  500 m
3668                  if (jk.eq.i1000) trc2d(ji,jj,63) = fregenfastsi(ji,jj)       !! Si regeneration to 1000 m
3669                  trc2d(ji,jj,64) = trc2d(ji,jj,64) + (freminn(ji,jj)  * fse3t(ji,jj,jk))        !! sum of fast-sinking N  fluxes
3670                  trc2d(ji,jj,65) = trc2d(ji,jj,65) + (freminsi(ji,jj) * fse3t(ji,jj,jk))        !! sum of fast-sinking Si fluxes
3671                  trc2d(ji,jj,66) = trc2d(ji,jj,66) + (freminfe(ji,jj) * fse3t(ji,jj,jk))        !! sum of fast-sinking Fe fluxes
3672                  trc2d(ji,jj,67) = trc2d(ji,jj,67) + (freminc(ji,jj)  * fse3t(ji,jj,jk))        !! sum of fast-sinking C  fluxes
3673                  trc2d(ji,jj,68) = trc2d(ji,jj,68) + (freminca(ji,jj) * fse3t(ji,jj,jk))        !! sum of fast-sinking Ca fluxes
3674                  if (jk.eq.mbathy(ji,jj)) then
3675                     trc2d(ji,jj,69) = fsedn(ji,jj)                                   !! N  sedimentation flux                                 
3676                     trc2d(ji,jj,70) = fsedsi(ji,jj)                                  !! Si sedimentation flux
3677                     trc2d(ji,jj,71) = fsedfe(ji,jj)                                  !! Fe sedimentation flux
3678                     trc2d(ji,jj,72) = fsedc(ji,jj)                                   !! C  sedimentation flux
3679                     trc2d(ji,jj,73) = fsedca(ji,jj)                                  !! Ca sedimentation flux
3680                  endif
3681                  if (jk.eq.1)  trc2d(ji,jj,74) = qsr(ji,jj)
3682                  if (jk.eq.1)  trc2d(ji,jj,75) = xpar(ji,jj,jk)
3683                  !! if (jk.eq.1)  trc2d(ji,jj,75) = real(iters(ji,jj))
3684                  !! diagnostic fields 76 to 80 calculated below
3685                  trc2d(ji,jj,81) = trc2d(ji,jj,81) + fprn_ml(ji,jj)           !! mixed layer non-diatom production
3686                  trc2d(ji,jj,82) = trc2d(ji,jj,82) + fprd_ml(ji,jj)           !! mixed layer     diatom production
3687# if defined key_gulf_finland
3688                  if (jk.eq.1)  trc2d(ji,jj,83) = real(ibio_switch)            !! Gulf of Finland check
3689# else
3690                  trc2d(ji,jj,83) = ocal_ccd(ji,jj)                            !! calcite CCD depth
3691# endif
3692                  trc2d(ji,jj,84) = fccd(ji,jj)                                !! last model level above calcite CCD depth
3693                  if (jk.eq.1)     trc2d(ji,jj,85) = xFree(ji,jj)              !! surface "free" iron
3694                  if (jk.eq.i0200) trc2d(ji,jj,86) = xFree(ji,jj)              !! "free" iron at  100 m
3695                  if (jk.eq.i0200) trc2d(ji,jj,87) = xFree(ji,jj)              !! "free" iron at  200 m
3696                  if (jk.eq.i0500) trc2d(ji,jj,88) = xFree(ji,jj)              !! "free" iron at  500 m
3697                  if (jk.eq.i1000) trc2d(ji,jj,89) = xFree(ji,jj)              !! "free" iron at 1000 m
3698                  !! AXY (27/06/12): extract "euphotic depth"
3699                  if (jk.eq.1)     trc2d(ji,jj,90) = xze(ji,jj)
3700                  !!
3701# if defined key_roam
3702                  !! ROAM provisionally has access to a further 20 2D diagnostics
3703                  if (jk .eq. 1) then
3704                     trc2d(ji,jj,91)  = trc2d(ji,jj,91)  + wndm(ji,jj)              !! surface wind
3705                     trc2d(ji,jj,92)  = trc2d(ji,jj,92)  + f_pco2atm(ji,jj)           !! atmospheric pCO2
3706                     trc2d(ji,jj,93)  = trc2d(ji,jj,93)  + f_ph(ji,jj)                !! ocean pH
3707                     trc2d(ji,jj,94)  = trc2d(ji,jj,94)  + f_pco2w(ji,jj)             !! ocean pCO2
3708                     trc2d(ji,jj,95)  = trc2d(ji,jj,95)  + f_h2co3(ji,jj)             !! ocean H2CO3 conc.
3709                     trc2d(ji,jj,96)  = trc2d(ji,jj,96)  + f_hco3(ji,jj)              !! ocean HCO3 conc.
3710                     trc2d(ji,jj,97)  = trc2d(ji,jj,97)  + f_co3(ji,jj)               !! ocean CO3 conc.
3711                     trc2d(ji,jj,98)  = trc2d(ji,jj,98)  + f_co2flux(ji,jj)           !! air-sea CO2 flux
3712                     trc2d(ji,jj,99)  = trc2d(ji,jj,99)  + f_omcal(ji,jj)      !! ocean omega calcite
3713                     trc2d(ji,jj,100) = trc2d(ji,jj,100) + f_omarg(ji,jj)      !! ocean omega aragonite
3714                     trc2d(ji,jj,101) = trc2d(ji,jj,101) + f_TDIC(ji,jj)              !! ocean TDIC
3715                     trc2d(ji,jj,102) = trc2d(ji,jj,102) + f_TALK(ji,jj)              !! ocean TALK
3716                     trc2d(ji,jj,103) = trc2d(ji,jj,103) + f_kw660(ji,jj)             !! surface kw660
3717                     trc2d(ji,jj,104) = trc2d(ji,jj,104) + f_pp0(ji,jj)               !! surface pressure
3718                     trc2d(ji,jj,105) = trc2d(ji,jj,105) + f_o2flux(ji,jj)            !! air-sea O2 flux
3719                     trc2d(ji,jj,106) = trc2d(ji,jj,106) + f_o2sat(ji,jj)             !! ocean O2 saturation
3720                     trc2d(ji,jj,107) = f2_ccd_cal(ji,jj)                      !! depth calcite CCD
3721                     trc2d(ji,jj,108) = f2_ccd_arg(ji,jj)                      !! depth aragonite CCD
3722                  endif
3723                  if (jk .eq. mbathy(ji,jj)) then
3724                     trc2d(ji,jj,109) = f3_omcal(ji,jj,jk)                     !! seafloor omega calcite
3725                     trc2d(ji,jj,110) = f3_omarg(ji,jj,jk)                     !! seafloor omega aragonite
3726                  endif
3727                  !! diagnostic fields 111 to 117 calculated below
3728                  if (jk.eq.i0100) trc2d(ji,jj,118) = ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)  !! rain ratio at  100 m
3729                  if (jk.eq.i0500) trc2d(ji,jj,119) = ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)  !! rain ratio at  500 m
3730                  if (jk.eq.i1000) trc2d(ji,jj,120) = ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)  !! rain ratio at 1000 m
3731                  !! AXY (18/01/12): benthic flux diagnostics
3732                  if (jk.eq.mbathy(ji,jj)) then
3733                     trc2d(ji,jj,121) = f_sbenin_n(ji,jj)  + f_fbenin_n(ji,jj)
3734                     trc2d(ji,jj,122) = f_sbenin_fe(ji,jj) + f_fbenin_fe(ji,jj)
3735                     trc2d(ji,jj,123) = f_sbenin_c(ji,jj)  + f_fbenin_c(ji,jj)
3736                     trc2d(ji,jj,124) = f_fbenin_si(ji,jj)
3737                     trc2d(ji,jj,125) = f_fbenin_ca(ji,jj)
3738                     trc2d(ji,jj,126) = f_benout_n(ji,jj)
3739                     trc2d(ji,jj,127) = f_benout_fe(ji,jj)
3740                     trc2d(ji,jj,128) = f_benout_c(ji,jj)
3741                     trc2d(ji,jj,129) = f_benout_si(ji,jj)
3742                     trc2d(ji,jj,130) = f_benout_ca(ji,jj)
3743                  endif
3744                  !! diagnostics fields 131 to 135 calculated below
3745                  trc2d(ji,jj,136) = f_runoff(ji,jj)
3746                  !! AXY (19/07/12): amended to allow for riverine nutrient addition below surface
3747                  trc2d(ji,jj,137) = trc2d(ji,jj,137) + (f_riv_loc_n(ji,jj) * fse3t(ji,jj,jk))
3748                  trc2d(ji,jj,138) = trc2d(ji,jj,138) + (f_riv_loc_si(ji,jj) * fse3t(ji,jj,jk))
3749                  trc2d(ji,jj,139) = trc2d(ji,jj,139) + (f_riv_loc_c(ji,jj) * fse3t(ji,jj,jk))
3750                  trc2d(ji,jj,140) = trc2d(ji,jj,140) + (f_riv_loc_alk(ji,jj) * fse3t(ji,jj,jk))
3751                  trc2d(ji,jj,141) = trc2d(ji,jj,141) + (fslowc(ji,jj)  * fse3t(ji,jj,jk))       !! slow sinking detritus C production
3752                  if (jk.eq.i0100) trc2d(ji,jj,142) = fslowcflux(ji,jj)        !! slow detritus flux at  100 m
3753                  if (jk.eq.i0200) trc2d(ji,jj,143) = fslowcflux(ji,jj)        !! slow detritus flux at  200 m
3754                  if (jk.eq.i0500) trc2d(ji,jj,144) = fslowcflux(ji,jj)        !! slow detritus flux at  500 m
3755                  if (jk.eq.i1000) trc2d(ji,jj,145) = fslowcflux(ji,jj)        !! slow detritus flux at 1000 m
3756                  trc2d(ji,jj,146)  = trc2d(ji,jj,146)  + ftot_c(ji,jj)        !! carbon     inventory
3757                  trc2d(ji,jj,147)  = trc2d(ji,jj,147)  + ftot_a(ji,jj)        !! alkalinity inventory
3758                  trc2d(ji,jj,148)  = trc2d(ji,jj,148)  + ftot_o2(ji,jj)       !! oxygen     inventory
3759                  if (jk.eq.mbathy(ji,jj)) then
3760                     trc2d(ji,jj,149) = f_benout_lyso_ca(ji,jj)
3761                  endif
3762                  trc2d(ji,jj,150) = fcomm_resp(ji,jj) * fse3t(ji,jj,jk)                  !! community respiration
3763        !!
3764        !! AXY (14/02/14): a Valentines Day gift to BASIN - a shedload of new
3765                  !!                 diagnostics that they'll most likely never need!
3766                  !!                 (actually, as with all such gifts, I'm giving them
3767                  !!                 some things I'd like myself!)
3768                  !!
3769                  !! ----------------------------------------------------------------------
3770                  !! linear losses
3771                  !! non-diatom
3772                  trc2d(ji,jj,151) = trc2d(ji,jj,151) + (fdpn2(ji,jj)  * fse3t(ji,jj,jk))
3773                  !! diatom
3774                  trc2d(ji,jj,152) = trc2d(ji,jj,152) + (fdpd2(ji,jj)  * fse3t(ji,jj,jk))
3775                  !! microzooplankton
3776                  trc2d(ji,jj,153) = trc2d(ji,jj,153) + (fdzmi2(ji,jj) * fse3t(ji,jj,jk))
3777                  !! mesozooplankton
3778                  trc2d(ji,jj,154) = trc2d(ji,jj,154) + (fdzme2(ji,jj) * fse3t(ji,jj,jk))
3779                  !! ----------------------------------------------------------------------
3780                  !! microzooplankton grazing
3781                  !! microzooplankton messy -> N
3782                  trc2d(ji,jj,155) = trc2d(ji,jj,155) + (xphi * (fgmipn(ji,jj) + fgmid(ji,jj)) * fse3t(ji,jj,jk))
3783                  !! microzooplankton messy -> D
3784                  trc2d(ji,jj,156) = trc2d(ji,jj,156) + ((1. - xbetan) * finmi(ji,jj) * fse3t(ji,jj,jk))
3785                  !! microzooplankton messy -> DIC
3786                  trc2d(ji,jj,157) = trc2d(ji,jj,157) + (xphi * ((xthetapn * fgmipn(ji,jj)) + fgmidc(ji,jj)) * fse3t(ji,jj,jk))
3787                  !! microzooplankton messy -> Dc
3788                  trc2d(ji,jj,158) = trc2d(ji,jj,158) + ((1. - xbetac) * ficmi(ji,jj) * fse3t(ji,jj,jk))
3789                  !! microzooplankton excretion
3790                  trc2d(ji,jj,159) = trc2d(ji,jj,159) + (fmiexcr(ji,jj) * fse3t(ji,jj,jk))
3791                  !! microzooplankton respiration
3792                  trc2d(ji,jj,160) = trc2d(ji,jj,160) + (fmiresp(ji,jj) * fse3t(ji,jj,jk))
3793                  !! microzooplankton growth
3794                  trc2d(ji,jj,161) = trc2d(ji,jj,161) + (fmigrow(ji,jj) * fse3t(ji,jj,jk))
3795                  !! ----------------------------------------------------------------------
3796                  !! mesozooplankton grazing
3797                  !! mesozooplankton messy -> N
3798                  trc2d(ji,jj,162) = trc2d(ji,jj,162) + (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj)) * fse3t(ji,jj,jk))
3799                  !! mesozooplankton messy -> D
3800                  trc2d(ji,jj,163) = trc2d(ji,jj,163) + ((1. - xbetan) * finme(ji,jj) * fse3t(ji,jj,jk))
3801                  !! mesozooplankton messy -> DIC
3802                  trc2d(ji,jj,164) = trc2d(ji,jj,164) + (xphi * ((xthetapn * fgmepn(ji,jj)) + (xthetapd * fgmepd(ji,jj)) + &
3803                  &                  (xthetazmi * fgmezmi(ji,jj)) + fgmedc(ji,jj)) * fse3t(ji,jj,jk))
3804                  !! mesozooplankton messy -> Dc
3805                  trc2d(ji,jj,165) = trc2d(ji,jj,165) + ((1. - xbetac) * ficme(ji,jj) * fse3t(ji,jj,jk))
3806                  !! mesozooplankton excretion
3807                  trc2d(ji,jj,166) = trc2d(ji,jj,166) + (fmeexcr(ji,jj) * fse3t(ji,jj,jk))
3808                  !! mesozooplankton respiration
3809                  trc2d(ji,jj,167) = trc2d(ji,jj,167) + (fmeresp(ji,jj) * fse3t(ji,jj,jk))
3810                  !! mesozooplankton growth
3811                  trc2d(ji,jj,168) = trc2d(ji,jj,168) + (fmegrow(ji,jj) * fse3t(ji,jj,jk))
3812                  !! ----------------------------------------------------------------------
3813                  !! miscellaneous
3814                  trc2d(ji,jj,169) = trc2d(ji,jj,169) + (fddc(ji,jj)    * fse3t(ji,jj,jk)) !! detrital C remineralisation
3815                  trc2d(ji,jj,170) = trc2d(ji,jj,170) + (fgmidc(ji,jj)  * fse3t(ji,jj,jk)) !! microzoo grazing on detrital carbon
3816                  trc2d(ji,jj,171) = trc2d(ji,jj,171) + (fgmedc(ji,jj)  * fse3t(ji,jj,jk)) !! mesozoo  grazing on detrital carbon
3817                  !!
3818                  !! ----------------------------------------------------------------------
3819        !!
3820        !! AXY (23/10/14): extract primary production related surface fields to
3821        !!                 deal with diel cycle issues; hijacking BASIN 150m
3822        !!                 diagnostics to do so (see commented out diagnostics
3823        !!                 below this section)
3824        !!
3825                  !! extract relevant BASIN fields at 150m
3826                  if (jk .eq. i0150) then
3827                     trc2d(ji,jj,172) = trc2d(ji,jj,4)    !! Pn PP
3828                     trc2d(ji,jj,173) = trc2d(ji,jj,151)  !! Pn linear loss
3829                     trc2d(ji,jj,174) = trc2d(ji,jj,5)    !! Pn non-linear loss
3830                     trc2d(ji,jj,175) = trc2d(ji,jj,11)   !! Pn grazing to Zmi
3831                     trc2d(ji,jj,176) = trc2d(ji,jj,14)   !! Pn grazing to Zme
3832                     trc2d(ji,jj,177) = trc2d(ji,jj,6)    !! Pd PP
3833                     trc2d(ji,jj,178) = trc2d(ji,jj,152)  !! Pd linear loss
3834                     trc2d(ji,jj,179) = trc2d(ji,jj,7)    !! Pd non-linear loss
3835                     trc2d(ji,jj,180) = trc2d(ji,jj,15)   !! Pd grazing to Zme
3836                     trc2d(ji,jj,181) = trc2d(ji,jj,12)   !! Zmi grazing on D
3837                     trc2d(ji,jj,182) = trc2d(ji,jj,170)  !! Zmi grazing on Dc
3838                     trc2d(ji,jj,183) = trc2d(ji,jj,155)  !! Zmi messy feeding loss to N
3839                     trc2d(ji,jj,184) = trc2d(ji,jj,156)  !! Zmi messy feeding loss to D
3840                     trc2d(ji,jj,185) = trc2d(ji,jj,157)  !! Zmi messy feeding loss to DIC
3841                     trc2d(ji,jj,186) = trc2d(ji,jj,158)  !! Zmi messy feeding loss to Dc
3842                     trc2d(ji,jj,187) = trc2d(ji,jj,159)  !! Zmi excretion
3843                     trc2d(ji,jj,188) = trc2d(ji,jj,160)  !! Zmi respiration
3844                     trc2d(ji,jj,189) = trc2d(ji,jj,161)  !! Zmi growth
3845                     trc2d(ji,jj,190) = trc2d(ji,jj,153)  !! Zmi linear loss
3846                     trc2d(ji,jj,191) = trc2d(ji,jj,13)   !! Zmi non-linear loss
3847                     trc2d(ji,jj,192) = trc2d(ji,jj,16)   !! Zmi grazing to Zme
3848                     trc2d(ji,jj,193) = trc2d(ji,jj,17)   !! Zme grazing on D
3849                     trc2d(ji,jj,194) = trc2d(ji,jj,171)  !! Zme grazing on Dc
3850                     trc2d(ji,jj,195) = trc2d(ji,jj,162)  !! Zme messy feeding loss to N
3851                     trc2d(ji,jj,196) = trc2d(ji,jj,163)  !! Zme messy feeding loss to D
3852                     trc2d(ji,jj,197) = trc2d(ji,jj,164)  !! Zme messy feeding loss to DIC
3853                     trc2d(ji,jj,198) = trc2d(ji,jj,165)  !! Zme messy feeding loss to Dc
3854                     trc2d(ji,jj,199) = trc2d(ji,jj,166)  !! Zme excretion
3855                     trc2d(ji,jj,200) = trc2d(ji,jj,167)  !! Zme respiration
3856                     trc2d(ji,jj,201) = trc2d(ji,jj,168)  !! Zme growth
3857                     trc2d(ji,jj,202) = trc2d(ji,jj,154)  !! Zme linear loss
3858                     trc2d(ji,jj,203) = trc2d(ji,jj,18)   !! Zme non-linear loss
3859                     trc2d(ji,jj,204) = trc2d(ji,jj,20)   !! Slow detritus production, N
3860                     trc2d(ji,jj,205) = trc2d(ji,jj,21)   !! Slow detritus remineralisation, N
3861                     trc2d(ji,jj,206) = trc2d(ji,jj,141)  !! Slow detritus production, C
3862                     trc2d(ji,jj,207) = trc2d(ji,jj,169)  !! Slow detritus remineralisation, C
3863                     trc2d(ji,jj,208) = trc2d(ji,jj,43)   !! Fast detritus production, N
3864                     trc2d(ji,jj,209) = trc2d(ji,jj,21)   !! Fast detritus remineralisation, N
3865                     trc2d(ji,jj,210) = trc2d(ji,jj,64)   !! Fast detritus production, C
3866                     trc2d(ji,jj,211) = trc2d(ji,jj,67)   !! Fast detritus remineralisation, C
3867                     trc2d(ji,jj,212) = trc2d(ji,jj,150)  !! Community respiration
3868                     trc2d(ji,jj,213) = fslownflux(ji,jj) !! Slow detritus N flux at 150 m
3869                     trc2d(ji,jj,214) = fslowcflux(ji,jj) !! Slow detritus C flux at 150 m
3870                     trc2d(ji,jj,215) = ffastn(ji,jj)     !! Fast detritus N flux at 150 m
3871                     trc2d(ji,jj,216) = ffastc(ji,jj)     !! Fast detritus C flux at 150 m
3872                  endif
3873                  !!
3874                  !! Jpalm (11-08-2014)
3875                  !! Add UKESM1 diagnoatics
3876                  !!^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
3877                  if ((jk .eq. 1) .and.( jdms.eq.1)) then
3878                     trc2d(ji,jj,221) = dms_surf(ji,jj)          !! DMS surface concentration
3879                     !! AXY (13/03/15): add in other DMS estimates
3880                     trc2d(ji,jj,222) = dms_andr(ji,jj)          !! DMS surface concentration
3881                     trc2d(ji,jj,223) = dms_simo(ji,jj)          !! DMS surface concentration
3882                     trc2d(ji,jj,224) = dms_aran(ji,jj)          !! DMS surface concentration
3883                     trc2d(ji,jj,225) = dms_hall(ji,jj)          !! DMS surface concentration
3884                  endif
3885# endif
3886                  !! other possible future diagnostics include:
3887                  !!   - integrated tracer values (esp. biological)
3888                  !!   - mixed layer tracer values
3889                  !!   - sub-surface chlorophyll maxima (plus depth)
3890                  !!   - different mixed layer depth criteria (T, sigma, var. sigma)
3891
3892                  !!----------------------------------------------------------------------
3893                  !! Prepare 3D diagnostics
3894                  !!----------------------------------------------------------------------
3895                  !!
3896                  trc3d(ji,jj,jk,1)  = ((fprn(ji,jj) + fprd(ji,jj)) * zphn(ji,jj))     !! primary production 
3897                  trc3d(ji,jj,jk,2)  = fslownflux(ji,jj) + ffastn(ji,jj) !! detrital flux
3898                  trc3d(ji,jj,jk,3)  = fregen(ji,jj) + (freminn(ji,jj) * fse3t(ji,jj,jk))  !! remineralisation
3899# if defined key_roam
3900                  trc3d(ji,jj,jk,4)  = f3_pH(ji,jj,jk)            !! pH
3901                  trc3d(ji,jj,jk,5)  = f3_omcal(ji,jj,jk)         !! omega calcite
3902# else
3903                  trc3d(ji,jj,jk,4)  = ffastsi(ji,jj)             !! fast Si flux
3904# endif
3905             ENDIF   ! end of ln_diatrc option
3906             !! CLOSE wet point IF..THEN loop
3907            endif
3908         !! CLOSE horizontal loops
3909         ENDDO
3910         ENDDO
3911         !!
3912             IF( lk_iomput  .AND.  .NOT.  ln_diatrc  ) THEN
3913                 !! first - 2D diag implemented
3914                 !!         on every K level
3915                 !!-----------------------------------------
3916                 !!  --
3917                 !!second - 2d specific k level diags
3918                 !!
3919                 !!-----------------------------------------
3920                 IF (jk.eq.1) THEN
3921#   if defined key_debug_medusa
3922                     IF (lwp) write (numout,*) 'trc_bio_medusa: diag jk = 1'
3923                     CALL flush(numout)
3924#   endif
3925                     IF( med_diag%MED_QSR%dgsave ) THEN
3926                         CALL iom_put( "MED_QSR"  , qsr ) !
3927                     ENDIF
3928                     IF( med_diag%MED_XPAR%dgsave ) THEN
3929                         CALL iom_put( "MED_XPAR"  , xpar(:,:,jk) ) !
3930                     ENDIF       
3931                     IF( med_diag%OCAL_CCD%dgsave ) THEN
3932                         CALL iom_put( "OCAL_CCD"  , ocal_ccd ) !
3933                     ENDIF
3934                     IF( med_diag%FE_0000%dgsave ) THEN
3935                         CALL iom_put( "FE_0000"  , xFree ) !
3936                     ENDIF                     
3937                     IF( med_diag%MED_XZE%dgsave ) THEN
3938                         CALL iom_put( "MED_XZE"  , xze ) !
3939                     ENDIF 
3940# if defined key_roam                     
3941                     IF( med_diag%WIND%dgsave ) THEN
3942                         CALL iom_put( "WIND"  , wndm )
3943                     ENDIF
3944                     IF( med_diag%ATM_PCO2%dgsave ) THEN
3945                         CALL iom_put( "ATM_PCO2"  , f_pco2a2d )
3946                         CALL wrk_dealloc( jpi, jpj,    f_pco2a2d  )
3947                     ENDIF
3948                     IF( med_diag%OCN_PH%dgsave ) THEN
3949                         zw2d(:,:) = f3_pH(:,:,jk)
3950                         CALL iom_put( "OCN_PH"  , zw2d )
3951                     ENDIF
3952                     IF( med_diag%OCN_PCO2%dgsave ) THEN
3953                        CALL iom_put( "OCN_PCO2"  , f_pco2w2d )
3954                        CALL wrk_dealloc( jpi, jpj,   f_pco2w2d   )
3955                     ENDIF
3956                     IF( med_diag%OCNH2CO3%dgsave ) THEN
3957                         zw2d(:,:) = f3_h2co3(:,:,jk)
3958                         CALL iom_put( "OCNH2CO3"  , zw2d )
3959                     ENDIF
3960                     IF( med_diag%OCN_HCO3%dgsave ) THEN
3961                         zw2d(:,:) = f3_hco3(:,:,jk)
3962                         CALL iom_put( "OCN_HCO3"  , zw2d )
3963                     ENDIF
3964                     IF( med_diag%OCN_CO3%dgsave ) THEN
3965                         zw2d(:,:) = f3_co3(:,:,jk)
3966                         CALL iom_put( "OCN_CO3"  , zw2d )
3967                     ENDIF
3968                     IF( med_diag%CO2FLUX%dgsave ) THEN
3969                        CALL iom_put( "CO2FLUX"  , f_co2flux2d )
3970                        CALL wrk_dealloc( jpi, jpj,   f_co2flux2d   )
3971                     ENDIF
3972                     !!
3973                     !! AXY (10/11/16): repeat CO2 flux diagnostic in UKMO/CMIP6 units; this
3974                     !!                 both outputs the CO2 flux in specified units and
3975                     !!                 sends the resulting field to the coupler
3976                     !! JPALM (17/11/16): put CO2 flux (fgco2) alloc/unalloc/pass to zn
3977                     !!                 out of diag list request
3978                     CALL lbc_lnk( fgco2(:,:),'T',1. )
3979                     IF( med_diag%FGCO2%dgsave ) THEN
3980                         CALL iom_put( "FGCO2"  , fgco2 )
3981                     ENDIF
3982                     !! JPALM (17/11/16): should mv this fgco2 part
3983                     !!                   out of lk_iomput loop
3984                     zb_co2_flx = zn_co2_flx
3985                     zn_co2_flx = fgco2
3986                     IF (lk_oasis) THEN
3987                        CO2Flux_out_cpl = zn_co2_flx
3988                     ENDIF
3989                     CALL wrk_dealloc( jpi, jpj,   fgco2   )
3990                     !! ---
3991                     IF( med_diag%OM_CAL%dgsave ) THEN
3992                         CALL iom_put( "OM_CAL"  , f_omcal )
3993                     ENDIF
3994                     IF( med_diag%OM_ARG%dgsave ) THEN
3995                         CALL iom_put( "OM_ARG"  , f_omarg )
3996                     ENDIF
3997                     IF( med_diag%TCO2%dgsave ) THEN
3998                         CALL iom_put( "TCO2"  , f_TDIC2d )
3999                         CALL wrk_dealloc( jpi, jpj,   f_TDIC2d   )
4000                     ENDIF
4001                     IF( med_diag%TALK%dgsave ) THEN
4002                         CALL iom_put( "TALK"  , f_TALK2d )
4003                         CALL wrk_dealloc( jpi, jpj,    f_TALK2d  )
4004                     ENDIF
4005                     IF( med_diag%KW660%dgsave ) THEN
4006                         CALL iom_put( "KW660"  , f_kw6602d )
4007                         CALL wrk_dealloc( jpi, jpj,   f_kw6602d   )
4008                     ENDIF
4009                     IF( med_diag%ATM_PP0%dgsave ) THEN
4010                         CALL iom_put( "ATM_PP0"  , f_pp02d )
4011                         CALL wrk_dealloc( jpi, jpj,    f_pp02d  )
4012                     ENDIF
4013                     IF( med_diag%O2FLUX%dgsave ) THEN
4014                         CALL iom_put( "O2FLUX"  , f_o2flux2d )
4015                         CALL wrk_dealloc( jpi, jpj,   f_o2flux2d   )
4016                     ENDIF
4017                     IF( med_diag%O2SAT%dgsave ) THEN
4018                         CALL iom_put( "O2SAT"  , f_o2sat2d )
4019                         CALL wrk_dealloc( jpi, jpj,  f_o2sat2d    )
4020                     ENDIF
4021                     IF( med_diag%CAL_CCD%dgsave ) THEN
4022                         CALL iom_put( "CAL_CCD"  , f2_ccd_cal )
4023                     ENDIF
4024                     IF( med_diag%ARG_CCD%dgsave ) THEN
4025                         CALL iom_put( "ARG_CCD"  , f2_ccd_arg )
4026                     ENDIF
4027                     IF (jdms .eq. 1) THEN
4028                       IF( med_diag%DMS_SURF%dgsave ) THEN
4029                         CALL lbc_lnk(dms_surf2d(:,:),'T',1. )
4030                         CALL iom_put( "DMS_SURF"  , dms_surf2d )
4031                         zb_dms_srf = zn_dms_srf
4032                         zn_dms_srf = dms_surf2d
4033                         IF (lk_oasis) THEN
4034                            DMS_out_cpl = zn_dms_srf
4035                         ENDIF
4036                         CALL wrk_dealloc( jpi, jpj,   dms_surf2d   ) 
4037                       ENDIF
4038                       IF( med_diag%DMS_ANDR%dgsave ) THEN
4039                         CALL iom_put( "DMS_ANDR"  , dms_andr2d )
4040                         CALL wrk_dealloc( jpi, jpj,   dms_andr2d   )
4041                       ENDIF
4042                       IF( med_diag%DMS_SIMO%dgsave ) THEN
4043                         CALL iom_put( "DMS_SIMO"  , dms_simo2d )
4044                         CALL wrk_dealloc( jpi, jpj,    dms_simo2d  )
4045                       ENDIF
4046                       IF( med_diag%DMS_ARAN%dgsave ) THEN
4047                         CALL iom_put( "DMS_ARAN"  , dms_aran2d )
4048                         CALL wrk_dealloc( jpi, jpj,   dms_aran2d   )
4049                       ENDIF
4050                       IF( med_diag%DMS_HALL%dgsave ) THEN
4051                         CALL iom_put( "DMS_HALL"  , dms_hall2d )
4052                         CALL wrk_dealloc( jpi, jpj,   dms_hall2d   )
4053                       ENDIF
4054                     ENDIF
4055                     !! AXY (24/11/16): extra MOCSY diagnostics
4056                     IF( med_diag%ATM_XCO2%dgsave ) THEN
4057                        CALL iom_put( "ATM_XCO2"  ,   f_xco2a_2d      )
4058                        CALL wrk_dealloc( jpi, jpj,   f_xco2a_2d      )
4059                     ENDIF
4060                     IF( med_diag%OCN_FCO2%dgsave ) THEN
4061                        CALL iom_put( "OCN_FCO2"  ,   f_fco2w_2d      )
4062                        CALL wrk_dealloc( jpi, jpj,   f_fco2w_2d      )
4063                     ENDIF
4064                     IF( med_diag%ATM_FCO2%dgsave ) THEN
4065                        CALL iom_put( "ATM_FCO2"  ,   f_fco2a_2d      )
4066                        CALL wrk_dealloc( jpi, jpj,   f_fco2a_2d      )
4067                     ENDIF
4068                     IF( med_diag%OCN_RHOSW%dgsave ) THEN
4069                        CALL iom_put( "OCN_RHOSW"  ,  f_ocnrhosw_2d   )
4070                        CALL wrk_dealloc( jpi, jpj,   f_ocnrhosw_2d   )
4071                     ENDIF
4072                     IF( med_diag%OCN_SCHCO2%dgsave ) THEN
4073                        CALL iom_put( "OCN_SCHCO2"  , f_ocnschco2_2d  )
4074                        CALL wrk_dealloc( jpi, jpj,   f_ocnschco2_2d  )
4075                     ENDIF
4076                     IF( med_diag%OCN_KWCO2%dgsave ) THEN
4077                        CALL iom_put( "OCN_KWCO2"  ,  f_ocnkwco2_2d   )
4078                        CALL wrk_dealloc( jpi, jpj,   f_ocnkwco2_2d   )
4079                     ENDIF
4080                     IF( med_diag%OCN_K0%dgsave ) THEN
4081                        CALL iom_put( "OCN_K0"  ,     f_ocnk0_2d      )
4082                        CALL wrk_dealloc( jpi, jpj,   f_ocnk0_2d      )
4083                     ENDIF
4084                     IF( med_diag%CO2STARAIR%dgsave ) THEN
4085                        CALL iom_put( "CO2STARAIR"  , f_co2starair_2d )
4086                        CALL wrk_dealloc( jpi, jpj,   f_co2starair_2d )
4087                     ENDIF
4088                     IF( med_diag%OCN_DPCO2%dgsave ) THEN
4089                        CALL iom_put( "OCN_DPCO2"  ,  f_ocndpco2_2d   )
4090                        CALL wrk_dealloc( jpi, jpj,   f_ocndpco2_2d   )
4091                     ENDIF
4092# endif                     
4093                 ELSE IF (jk.eq.i0100) THEN 
4094#   if defined key_debug_medusa
4095                     IF (lwp) write (numout,*) 'trc_bio_medusa: diag jk = 100'
4096                     CALL flush(numout)
4097#   endif
4098                     IF( med_diag%SDT__100%dgsave ) THEN
4099                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk)
4100                        CALL iom_put( "SDT__100"  , zw2d )
4101                     ENDIF
4102                     IF( med_diag%REG__100%dgsave ) THEN
4103                        CALL iom_put( "REG__100"  , fregen2d )
4104                     ENDIF
4105                     IF( med_diag%FDT__100%dgsave ) THEN
4106                        CALL iom_put( "FDT__100"  , ffastn )
4107                     ENDIF           
4108                     IF( med_diag%RG__100F%dgsave ) THEN
4109                        CALL iom_put( "RG__100F"  , fregenfast )
4110                     ENDIF
4111                     IF( med_diag%FDS__100%dgsave ) THEN
4112                        CALL iom_put( "FDS__100"  , ffastsi )
4113                     ENDIF         
4114                     IF( med_diag%RGS_100F%dgsave ) THEN
4115                        CALL iom_put( "RGS_100F"  , fregenfastsi )
4116                     ENDIF
4117                     IF( med_diag%FE_0100%dgsave ) THEN
4118                        CALL iom_put( "FE_0100"  , xFree )
4119                     ENDIF
4120# if defined key_roam                     
4121                     IF( med_diag%RR_0100%dgsave ) THEN
4122                        CALL iom_put( "RR_0100"  , ffastca2d )
4123                     ENDIF                     
4124                     IF( med_diag%SDC__100%dgsave ) THEN
4125                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk)
4126                        CALL iom_put( "SDC__100"  , zw2d )
4127                     ENDIF                 
4128                     IF( med_diag%epC100%dgsave    ) THEN
4129                        zw2d(:,:) = (fslowcflux + ffastc) * tmask(:,:,jk)
4130                        CALL iom_put( "epC100"    , zw2d )
4131                     ENDIF         
4132                     IF( med_diag%epCALC100%dgsave ) THEN
4133                        CALL iom_put( "epCALC100" , ffastca )
4134                     ENDIF         
4135                     IF( med_diag%epN100%dgsave    ) THEN
4136                        zw2d(:,:) = (fslownflux + ffastn) * tmask(:,:,jk)
4137                        CALL iom_put( "epN100"    , zw2d )
4138                     ENDIF         
4139                     IF( med_diag%epSI100%dgsave   ) THEN
4140                        CALL iom_put( "epSI100"   , ffastsi )
4141                     ENDIF         
4142                 ELSE IF (jk.eq.i0150) THEN
4143#   if defined key_debug_medusa
4144                     IF (lwp) write (numout,*) 'trc_bio_medusa: diag jk = 150'
4145                     CALL flush(numout)
4146#   endif
4147# endif                     
4148                 ELSE IF (jk.eq.i0200) THEN
4149#   if defined key_debug_medusa
4150                     IF (lwp) write (numout,*) 'trc_bio_medusa: diag jk = 200'
4151                     CALL flush(numout)
4152#   endif
4153                     IF( med_diag%SDT__200%dgsave ) THEN
4154                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk)
4155                        CALL iom_put( "SDT__200"  , zw2d )
4156                     ENDIF
4157                     IF( med_diag%REG__200%dgsave ) THEN
4158                        CALL iom_put( "REG__200"  , fregen2d )
4159                     ENDIF
4160                     IF( med_diag%FDT__200%dgsave ) THEN
4161                        CALL iom_put( "FDT__200"  , ffastn )
4162                     ENDIF
4163                     IF( med_diag%RG__200F%dgsave ) THEN
4164                        CALL iom_put( "RG__200F"  , fregenfast )
4165                     ENDIF
4166                     IF( med_diag%FDS__200%dgsave ) THEN
4167                        CALL iom_put( "FDS__200"  , ffastsi )
4168                     ENDIF
4169                     IF( med_diag%RGS_200F%dgsave ) THEN
4170                        CALL iom_put( "RGS_200F"  , fregenfastsi )
4171                     ENDIF
4172                     IF( med_diag%FE_0200%dgsave ) THEN
4173                        CALL iom_put( "FE_0200"   , xFree )
4174                     ENDIF
4175# if defined key_roam                     
4176                     IF( med_diag%SDC__200%dgsave ) THEN
4177                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk)
4178                        CALL iom_put( "SDC__200"  , zw2d )
4179                     ENDIF
4180# endif                     
4181                 ELSE IF (jk.eq.i0500) THEN
4182#   if defined key_debug_medusa
4183                     IF (lwp) write (numout,*) 'trc_bio_medusa: diag jk = 500'
4184                     CALL flush(numout)
4185#   endif
4186                     IF( med_diag%SDT__500%dgsave ) THEN
4187                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk)
4188                        CALL iom_put( "SDT__500"  , zw2d )
4189                     ENDIF
4190                     IF( med_diag%REG__500%dgsave ) THEN
4191                        CALL iom_put( "REG__500"  , fregen2d )
4192                     ENDIF     
4193                     IF( med_diag%FDT__500%dgsave ) THEN
4194                        CALL iom_put( "FDT__500"  , ffastn )
4195                     ENDIF
4196                     IF( med_diag%RG__500F%dgsave ) THEN
4197                        CALL iom_put( "RG__500F"  , fregenfast )
4198                     ENDIF
4199                     IF( med_diag%FDS__500%dgsave ) THEN
4200                        CALL iom_put( "FDS__500"  , ffastsi )
4201                     ENDIF
4202                     IF( med_diag%RGS_500F%dgsave ) THEN
4203                        CALL iom_put( "RGS_500F"  , fregenfastsi )
4204                     ENDIF
4205                     IF( med_diag%FE_0500%dgsave ) THEN
4206                        CALL iom_put( "FE_0500"  , xFree )
4207                     ENDIF
4208# if defined key_roam                     
4209                     IF( med_diag%RR_0500%dgsave ) THEN
4210                        CALL iom_put( "RR_0500"  , ffastca2d )
4211                     ENDIF
4212                     IF( med_diag%SDC__500%dgsave ) THEN
4213                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk)
4214                        CALL iom_put( "SDC__500"  , zw2d )
4215                     ENDIF 
4216# endif                     
4217                 ELSE IF (jk.eq.i1000) THEN
4218#   if defined key_debug_medusa
4219                     IF (lwp) write (numout,*) 'trc_bio_medusa: diag jk = 1000'
4220                     CALL flush(numout)
4221#   endif
4222                     IF( med_diag%SDT_1000%dgsave ) THEN
4223                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk)
4224                        CALL iom_put( "SDT_1000"  , zw2d )
4225                     ENDIF
4226                     IF( med_diag%REG_1000%dgsave ) THEN
4227                        CALL iom_put( "REG_1000"  , fregen2d )
4228                     ENDIF 
4229                     IF( med_diag%FDT_1000%dgsave ) THEN
4230                        CALL iom_put( "FDT_1000"  , ffastn )
4231                     ENDIF
4232                     IF( med_diag%RG_1000F%dgsave ) THEN
4233                        CALL iom_put( "RG_1000F"  , fregenfast )
4234                     ENDIF
4235                     IF( med_diag%FDS_1000%dgsave ) THEN
4236                        CALL iom_put( "FDS_1000"  , ffastsi )
4237                     ENDIF
4238                     IF( med_diag%RGS1000F%dgsave ) THEN
4239                        CALL iom_put( "RGS1000F"  , fregenfastsi )
4240                     ENDIF
4241                     IF( med_diag%FE_1000%dgsave ) THEN
4242                        CALL iom_put( "FE_1000"  , xFree )
4243                     ENDIF
4244# if defined key_roam                     
4245                     IF( med_diag%RR_1000%dgsave ) THEN
4246                        CALL iom_put( "RR_1000"  , ffastca2d )
4247                        CALL wrk_dealloc( jpi, jpj,  ffastca2d    )
4248                     ENDIF
4249                     IF( med_diag%SDC_1000%dgsave ) THEN
4250                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk)
4251                        CALL iom_put( "SDC_1000"  , zw2d )
4252                     ENDIF 
4253# endif                     
4254                 ENDIF
4255                 !! to do on every k loop :
4256                 IF( med_diag%DETFLUX3%dgsave ) THEN
4257                      detflux3d(:,:,jk) = (fslownflux(:,:) + ffastn(:,:)) * tmask(:,:,jk) !! detrital flux
4258                      !CALL iom_put( "DETFLUX3"  , ftot_n )
4259                 ENDIF
4260# if defined key_roam                     
4261                 IF( med_diag%EXPC3%dgsave ) THEN
4262                    expc3(:,:,jk) = (fslowcflux(:,:) + ffastc(:,:)) * tmask(:,:,jk)
4263                 ENDIF         
4264                 IF( med_diag%EXPN3%dgsave ) THEN
4265                    expn3(:,:,jk) = (fslownflux(:,:) + ffastn(:,:)) * tmask(:,:,jk)
4266                 ENDIF         
4267# endif         
4268              ENDIF
4269      !! CLOSE vertical loop
4270      ENDDO
4271
4272      !!----------------------------------------------------------------------
4273      !! Final calculations for diagnostics
4274      !!----------------------------------------------------------------------
4275      CALL bio_medusa_fin( kt )
4276
4277# if defined key_trc_diabio
4278       !! Lateral boundary conditions on trcbio
4279       DO jn=1,jp_medusa_trd
4280          CALL lbc_lnk(trbio(:,:,1,jn),'T',1. )
4281       ENDDO 
4282# endif
4283
4284# if defined key_debug_medusa
4285       IF(lwp) WRITE(numout,*) ' MEDUSA exiting trc_bio_medusa at kt =', kt
4286       CALL flush(numout)
4287# endif
4288
4289   END SUBROUTINE trc_bio_medusa
4290
4291#else
4292   !!======================================================================
4293   !!  Dummy module :                                   No MEDUSA bio-model
4294   !!======================================================================
4295CONTAINS
4296   SUBROUTINE trc_bio_medusa( kt )                   ! Empty routine
4297      INTEGER, INTENT( in ) ::   kt
4298      WRITE(*,*) 'trc_bio_medusa: You should not have seen this print! error?', kt
4299   END SUBROUTINE trc_bio_medusa
4300#endif 
4301
4302   !!======================================================================
4303END MODULE  trcbio_medusa
Note: See TracBrowser for help on using the repository browser.