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

Last change on this file since 7938 was 7938, checked in by marc, 8 years ago

Carbon chemistry has been pulled out of trcbio_medusa.F90 into carb_chem.F90

File size: 221.1 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 carb_chem_mod,              ONLY: carb_chem
101      USE bio_medusa_diag_slice_mod,  ONLY: bio_medusa_diag_slice
102      USE bio_medusa_fin_mod,         ONLY: bio_medusa_fin
103
104      IMPLICIT NONE
105      PRIVATE
106     
107      PUBLIC   trc_bio_medusa    ! called in trcsms_medusa.F90
108
109   !!* Substitution
110#  include "domzgr_substitute.h90"
111   !!----------------------------------------------------------------------
112   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
113   !! $Id$
114   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
115   !!----------------------------------------------------------------------
116
117CONTAINS
118
119   SUBROUTINE trc_bio_medusa( kt )
120      !!---------------------------------------------------------------------
121      !!                     ***  ROUTINE trc_bio  ***
122      !!
123      !! ** Purpose :   compute the now trend due to biogeochemical processes
124      !!              and add it to the general trend of passive tracers equations
125      !!
126      !! ** Method  :   each now biological flux is calculated in function of now
127      !!              concentrations of tracers.
128      !!              depending on the tracer, these fluxes are sources or sinks.
129      !!              the total of the sources and sinks for each tracer
130      !!              is added to the general trend.
131      !!       
132      !!                      tra = tra + zf...tra - zftra...
133      !!                                     |         |
134      !!                                     |         |
135      !!                                  source      sink
136      !!       
137      !!              IF 'key_trc_diabio' defined , the biogeochemical trends
138      !!              for passive tracers are saved for futher diagnostics.
139      !!---------------------------------------------------------------------
140      !!
141      !!
142      !!----------------------------------------------------------------------           
143      !! Variable conventions
144      !!----------------------------------------------------------------------
145      !!
146      !! names: z*** - state variable
147      !!        f*** - function (or temporary variable used in part of a function)
148      !!        x*** - parameter
149      !!        b*** - right-hand part (sources and sinks)
150      !!        i*** - integer variable (usually used in yes/no flags)
151      !!
152      !! time (integer timestep)
153      INTEGER, INTENT( in ) ::    kt
154      !!
155      !! spatial array indices
156      INTEGER  ::    ji,jj,jk,jn
157      !!
158      !! AXY (27/07/10): add in indices for depth horizons (for sinking flux
159      !!                 and seafloor iron inputs)
160      !! INTEGER  ::    i0100, i0200, i0500, i1000, i1100
161      !!
162      !! model state variables
163!      REAL(wp), DIMENSION(jpi,jpj) ::    zchn,zchd,zphn,zphd,zpds,zzmi
164!      REAL(wp), DIMENSION(jpi,jpj) ::    zzme,zdet,zdtc,zdin,zsil,zfer
165! zage doesn't seem to be used - marc 19/4/17
166!      REAL(wp) ::    zage
167!# if defined key_roam
168!      REAL(wp), DIMENSION(jpi,jpj) ::    zdic, zalk, zoxy
169!      REAL(wp), DIMENSION(jpi,jpj) ::    ztmp, zsal
170!# endif
171!# if defined key_mocsy
172!      REAL(wp), DIMENSION(jpi,jpj) ::    zpho
173!# endif
174      !!
175      !! integrated source and sink terms
176      REAL(wp) ::    b0
177      !! AXY (23/08/13): changed from individual variables for each flux to
178      !!                 an array that holds all fluxes
179      REAL(wp), DIMENSION(jpi,jpj,jp_medusa) ::    btra
180      !!
181      !! primary production and chl related quantities     
182      REAL(wp), DIMENSION(jpi,jpj) ::    fthetan,faln,fchn1,fchn,fjln,fprn,frn
183      REAL(wp), DIMENSION(jpi,jpj) ::    fthetad,fald,fchd1,fchd,fjld,fprd,frd
184      !! AXY (23/11/16): add in light-only limitation term (normalised 0-1 range)
185      REAL(wp), DIMENSION(jpi,jpj) ::    fjlim_pn, fjlim_pd
186      !! AXY (03/02/11): add in Liebig terms
187      REAL(wp), DIMENSION(jpi,jpj) ::    fpnlim, fpdlim
188      !! AXY (16/07/09): add in Eppley curve functionality
189      REAL(wp), DIMENSION(jpi,jpj) ::    fun_T,xvpnT,xvpdT
190      INTEGER  ::    ieppley
191      !! AXY (16/05/11): per Katya's prompting, add in new T-dependence
192      !!                 for phytoplankton growth only (i.e. no change
193      !!                 for remineralisation)
194      REAL(wp), DIMENSION(jpi,jpj) ::    fun_Q10
195      !! AXY (01/03/10): add in mixed layer PP diagnostics
196!      REAL(wp), DIMENSION(jpi,jpj) ::    fprn_ml,fprd_ml
197      !!
198      !! nutrient limiting factors
199      REAL(wp), DIMENSION(jpi,jpj) ::    fnln,ffln            !! N and Fe
200      REAL(wp), DIMENSION(jpi,jpj) ::    fnld,ffld,fsld,fsld2 !! N, Fe and Si
201      !!
202      !! silicon cycle
203      REAL(wp), DIMENSION(jpi,jpj) ::    fsin,fnsi,fprds,fsdiss
204      REAL(wp)                     ::    fsin1,fnsi1,fnsi2
205      !!
206      !! iron cycle; includes parameters for Parekh et al. (2005) iron scheme
207      REAL(wp), DIMENSION(jpi,jpj) ::    ffetop,ffebot,ffescav
208      REAL(wp) ::    xLgF, xFeT, xFeF, xFeL         !! state variables for iron-ligand system
209!      REAL(wp), DIMENSION(jpi,jpj) ::  xFree        !! state variables for iron-ligand system
210      REAL(wp) ::    xb_coef_tmp, xb2M4ac           !! iron-ligand parameters
211      REAL(wp) ::    xmaxFeF,fdeltaFe               !! max Fe' parameters
212      !!
213      !! local parameters for Moore et al. (2004) alternative scavenging scheme
214      REAL(wp) ::    fbase_scav,fscal_sink,fscal_part,fscal_scav
215      !!
216      !! local parameters for Moore et al. (2008) alternative scavenging scheme
217      REAL(wp) ::    fscal_csink,fscal_sisink,fscal_casink
218      !!
219      !! local parameters for Galbraith et al. (2010) alternative scavenging scheme
220      REAL(wp) ::    xCscav1, xCscav2, xk_org, xORGscav  !! organic portion of scavenging
221      REAL(wp) ::    xk_inorg, xINORGscav                !! inorganic portion of scavenging
222      !!
223      !! microzooplankton grazing
224      REAL(wp), DIMENSION(jpi,jpj) ::    fmi1,fmi,fgmipn,fgmid,fgmidc
225      REAL(wp), DIMENSION(jpi,jpj) ::    finmi,ficmi,fstarmi,fmith,fmigrow,fmiexcr,fmiresp
226      !!
227      !! mesozooplankton grazing
228      REAL(wp), DIMENSION(jpi,jpj) ::    fme1,fme,fgmepn,fgmepd,fgmepds,fgmezmi,fgmed,fgmedc
229      REAL(wp), DIMENSION(jpi,jpj) ::    finme,ficme,fstarme,fmeth,fmegrow,fmeexcr,fmeresp
230      !!
231      !! mortality/Remineralisation (defunct parameter "fz" removed)
232      REAL(wp), DIMENSION(jpi,jpj) ::    fdpn,fdpd,fdpds,fdzmi,fdzme,fdd
233# if defined key_roam
234      REAL(wp), DIMENSION(jpi,jpj) ::    fddc
235# endif
236      REAL(wp), DIMENSION(jpi,jpj) ::    fdpn2,fdpd2,fdpds2,fdzmi2,fdzme2
237      REAL(wp), DIMENSION(jpi,jpj) ::    fslown, fslowc
238!      REAL(wp), DIMENSION(jpi,jpj) ::    fslownflux, fslowcflux
239      REAL(wp), DIMENSION(jpi,jpj) ::    fregen,fregensi
240!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenfast,fregenfastsi
241# if defined key_roam
242!! Doesn't look like this is used - marc 10/4/17
243!!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenc
244!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenfastc
245# endif
246      !!
247      !! particle flux
248      REAL(WP), DIMENSION(jpi,jpj) ::    fdep1,fcaco3
249      REAL(WP), DIMENSION(jpi,jpj) ::    ftempn,ftempsi,ftempfe,ftempc,ftempca
250      REAL(wp), DIMENSION(jpi,jpj) ::    freminn,freminsi,freminfe,freminc,freminca
251!      REAL(wp), DIMENSION(jpi,jpj) ::    ffastn,ffastsi,ffastfe,ffastc,ffastca
252      REAL(wp), DIMENSION(jpi,jpj) ::    fprotf
253!      REAL(wp), DIMENSION(jpi,jpj) ::    fsedn,fsedsi,fsedfe,fsedc,fsedca
254!      REAL(wp), DIMENSION(jpi,jpj) ::    fccd
255      REAL(wp), DIMENSION(jpi,jpj) ::    fccd_dep
256      !!
257      !! AXY (06/07/11): alternative fast detritus schemes
258      REAL(wp) ::    fb_val, fl_sst
259      !!
260      !! AXY (08/07/11): fate of fast detritus reaching the seafloor
261! I don't think ffast2slowfe is used - marc 10/4/17
262!      REAL(wp), DIMENSION(jpi,jpj) ::    ffast2slown,ffast2slowfe,ffast2slowc
263      REAL(wp), DIMENSION(jpi,jpj) ::    ffast2slown,ffast2slowc
264      !!
265      !! conservation law
266      REAL(wp) ::    fnit0,fsil0,ffer0 
267# if defined key_roam
268      REAL(wp) ::    fcar0,falk0,foxy0 
269# endif     
270      !!
271      !! temporary variables
272      REAL(wp) ::    fq0,fq1,fq2,fq3,fq4,fq5,fq6,fq7,fq8,fq9
273      !!
274      !! water column nutrient and flux integrals
275!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_n,ftot_si,ftot_fe
276!      REAL(wp), DIMENSION(jpi,jpj) ::    fflx_n,fflx_si,fflx_fe
277!      REAL(wp), DIMENSION(jpi,jpj) ::    fifd_n,fifd_si,fifd_fe
278!      REAL(wp), DIMENSION(jpi,jpj) ::    fofd_n,fofd_si,fofd_fe
279# if defined key_roam
280!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_c,ftot_a,ftot_o2
281!      REAL(wp), DIMENSION(jpi,jpj) ::    fflx_c,fflx_a,fflx_o2
282!      REAL(wp), DIMENSION(jpi,jpj) ::    fifd_c,fifd_a,fifd_o2
283!      REAL(wp), DIMENSION(jpi,jpj) ::    fofd_c,fofd_a,fofd_o2
284# endif
285      !!
286      !! zooplankton grazing integrals
287!      REAL(wp), DIMENSION(jpi,jpj) ::    fzmi_i,fzmi_o,fzme_i,fzme_o
288      !!
289      !! limitation term temporary variables
290!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_pn,ftot_pd
291!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_zmi,ftot_zme,ftot_det,ftot_dtc
292      !! use ballast scheme (1) or simple exponential scheme (0; a conservation test)
293      INTEGER  ::    iball
294      !! use biological fluxes (1) or not (0)
295      INTEGER  ::    ibio_switch
296      !!
297      !! diagnose fluxes (should only be used in 1D runs)
298      INTEGER  ::    idf, idfval
299      !!
300      !! nitrogen and silicon production and consumption
301      REAL(wp) ::    fn_prod, fn_cons, fs_prod, fs_cons
302!      REAL(wp), DIMENSION(jpi,jpj) ::    fnit_prod, fnit_cons, fsil_prod, fsil_cons
303# if defined key_roam
304      !!
305      !! flags to help with calculating the position of the CCD
306      INTEGER, DIMENSION(jpi,jpj) ::     i2_omcal,i2_omarg
307      !!
308      !! AXY (24/11/16): add xCO2 variable for atmosphere (what we actually have)
309!      REAL(wp)                     ::    f_xco2a
310!      REAL(wp), DIMENSION(jpi,jpj) ::    f_ph, f_pco2w, f_h2co3, f_hco3, f_co3, f_co2flux
311!      REAL(wp), DIMENSION(jpi,jpj) ::    f_TDIC, f_TALK, f_dcf, f_henry
312!      REAL(wp), DIMENSION(jpi,jpj) ::    f_pp0
313!      REAL(wp), DIMENSION(jpi,jpj) ::    f_kw660, f_o2flux, f_o2sat
314      REAL(wp)                     ::    f_o2sat3
315!      REAL(wp), DIMENSION(jpi,jpj) ::    f_omcal, f_omarg
316      !!
317      !! AXY (23/06/15): additional diagnostics for MOCSY and oxygen
318!      REAL(wp), DIMENSION(jpi,jpj) ::    f_fco2w, f_BetaD, f_rhosw, f_opres, f_insitut, f_pco2atm, f_fco2atm
319!      REAL(wp), DIMENSION(jpi,jpj) ::    f_schmidtco2, f_kwco2, f_K0, f_co2starair, f_dpco2, f_kwo2
320      !! jpalm 14-07-2016: convert CO2flux diag from mmol/m2/d to kg/m2/s
321      REAL, PARAMETER :: weight_CO2_mol = 44.0095  !! g / mol
322      REAL, PARAMETER :: secs_in_day    = 86400.0  !! s / d
323      REAL, PARAMETER :: CO2flux_conv   = (1.e-6 * weight_CO2_mol) / secs_in_day
324
325      !!
326!      INTEGER, DIMENSION(jpi,jpj)  ::    iters
327      REAL(wp) ::    f_year
328      INTEGER  ::    i_year
329      INTEGER  ::    iyr1, iyr2
330      !!
331      !! carbon, alkalinity production and consumption
332      REAL(wp) ::    fc_prod, fc_cons, fa_prod, fa_cons
333!      REAL(wp), DIMENSION(jpi,jpj) ::    fcomm_resp
334!      REAL(wp), DIMENSION(jpi,jpj) ::    fcar_prod, fcar_cons
335      !!
336      !! oxygen production and consumption (and non-consumption)
337      REAL(wp), DIMENSION(jpi,jpj) ::    fo2_prod, fo2_cons, fo2_ncons, fo2_ccons
338!      REAL(wp), DIMENSION(jpi,jpj) ::    foxy_prod, foxy_cons, foxy_anox
339      !! Jpalm (11-08-2014)
340      !! add DMS in MEDUSA for UKESM1 model
341      REAL(wp), DIMENSION(jpi,jpj) ::    dms_surf
342      !! AXY (13/03/15): add in other DMS calculations
343      REAL(wp), DIMENSION(jpi,jpj) ::    dms_andr, dms_simo, dms_aran, dms_hall
344
345# endif
346      !!
347      !! benthic fluxes
348!      INTEGER  ::    ibenthic
349!      REAL(wp), DIMENSION(jpi,jpj) :: f_sbenin_n, f_sbenin_fe,              f_sbenin_c
350!      REAL(wp), DIMENSION(jpi,jpj) :: f_fbenin_n, f_fbenin_fe, f_fbenin_si, f_fbenin_c, f_fbenin_ca
351!      REAL(wp), DIMENSION(jpi,jpj) :: f_benout_n, f_benout_fe, f_benout_si, f_benout_c, f_benout_ca
352      REAL(wp) ::    zfact
353      !!
354      !! benthic fluxes of CaCO3 that shouldn't happen because of lysocline
355!      REAL(wp), DIMENSION(jpi,jpj) :: f_benout_lyso_ca
356      !!
357      !! riverine fluxes
358!      REAL(wp), DIMENSION(jpi,jpj) :: f_runoff, f_riv_n, f_riv_si, f_riv_c, f_riv_alk
359      !! AXY (19/07/12): variables for local riverine fluxes to handle inputs below surface
360      REAL(wp), DIMENSION(jpi,jpj) :: f_riv_loc_n, f_riv_loc_si, f_riv_loc_c, f_riv_loc_alk
361      !!---------------------------------------------------------------------
362
363# if defined key_debug_medusa
364      IF (lwp) write (numout,*) 'trc_bio_medusa: variables defined'
365      CALL flush(numout)
366# endif 
367
368      !! AXY (20/11/14): alter this to report on first MEDUSA call
369      !! IF( kt == nit000 ) THEN
370      IF( kt == nittrc000 ) THEN
371         IF(lwp) WRITE(numout,*)
372         IF(lwp) WRITE(numout,*) ' trc_bio: MEDUSA bio-model'
373         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
374    IF(lwp) WRITE(numout,*) ' kt =',kt
375      ENDIF
376
377      !! AXY (13/01/12): is benthic model properly interactive? 0 = no, 1 = yes
378      ibenthic = 1
379
380      !! not sure what this is for; it's not used anywhere; commenting out
381      !! fbodn(:,:) = 0.e0   
382
383      !!
384      IF( ln_diatrc ) THEN
385         !! blank 2D diagnostic array
386         trc2d(:,:,:) = 0.e0
387         !!
388         !! blank 3D diagnostic array
389         trc3d(:,:,:,:) = 0.e0
390      ENDIF
391
392      !!----------------------------------------------------------------------
393      !! b0 is present for debugging purposes; using b0 = 0 sets the tendency
394      !! terms of all biological equations to 0.
395      !!----------------------------------------------------------------------
396      !!
397      !! AXY (03/09/14): probably not the smartest move ever, but it'll fit
398      !!                 the bill for now; another item on the things-to-sort-
399      !!     out-in-the-future list ...
400# if defined key_kill_medusa
401      b0 = 0.
402# else
403      b0 = 1.
404# endif
405      !!----------------------------------------------------------------------
406      !! fast detritus ballast scheme (0 = no; 1 = yes)
407      !! alternative to ballast scheme is same scheme but with no ballast
408      !! protection (not dissimilar to Martin et al., 1987)
409      !!----------------------------------------------------------------------
410      !!
411      iball = 1
412
413      !!----------------------------------------------------------------------
414      !! full flux diagnostics (0 = no; 1 = yes); appear in ocean.output
415      !! these should *only* be used in 1D since they give comprehensive
416      !! output for ecological functions in the model; primarily used in
417      !! debugging
418      !!----------------------------------------------------------------------
419      !!
420      idf    = 0
421      !!
422      !! timer mechanism
423      if (kt/120*120.eq.kt) then
424         idfval = 1
425      else
426         idfval = 0
427      endif
428
429      !!----------------------------------------------------------------------
430      !! Initialise arrays to zero and set up arrays for diagnostics
431      !!----------------------------------------------------------------------
432! tmp - marc
433      write(numout,*) 'bbb13. before call to bio_medusa_init,kt=',kt
434      flush(numout)
435!
436      CALL bio_medusa_init( kt )
437! tmp - marc
438      write(numout,*) 'bbb14. after call to bio_medusa_init,kt=',kt
439      flush(numout)
440!
441       !!
442# if defined key_axy_nancheck
443       DO jn = 1,jptra
444          !! fq0 = MINVAL(trn(:,:,:,jn))
445          !! fq1 = MAXVAL(trn(:,:,:,jn))
446          fq2 = SUM(trn(:,:,:,jn))
447          !! if (lwp) write (numout,'(a,2i6,3(1x,1pe15.5))') 'NAN-CHECK', &
448          !! &        kt, jn, fq0, fq1, fq2
449          !! AXY (30/01/14): much to our surprise, the next line doesn't work on HECTOR
450          !!                 and has been replaced here with a specialist routine
451          !! if (fq2 /= fq2 ) then
452          if ( ieee_is_nan( fq2 ) ) then
453             !! there's a NaN here
454             if (lwp) write(numout,*) 'NAN detected in field', jn, 'at time', kt, 'at position:'
455             DO jk = 1,jpk
456                DO jj = 1,jpj
457                   DO ji = 1,jpi
458                      !! AXY (30/01/14): "isnan" problem on HECTOR
459                      !! if (trn(ji,jj,jk,jn) /= trn(ji,jj,jk,jn)) then
460                      if ( ieee_is_nan( trn(ji,jj,jk,jn) ) ) then
461                         if (lwp) write (numout,'(a,1pe12.2,4i6)') 'NAN-CHECK', &
462                         &        tmask(ji,jj,jk), ji, jj, jk, jn
463                      endif
464                   enddo
465                enddo
466             enddo
467             CALL ctl_stop( 'trcbio_medusa, NAN in incoming tracer field' )
468          endif
469       ENDDO
470       CALL flush(numout)
471# endif
472
473# if defined key_debug_medusa
474      IF (lwp) write (numout,*) 'trc_bio_medusa: variables initialised and checked'
475      CALL flush(numout)
476# endif 
477
478# if defined key_roam
479      !!----------------------------------------------------------------------
480      !! calculate atmospheric pCO2
481      !!----------------------------------------------------------------------
482      !!
483      !! what's atmospheric pCO2 doing? (data start in 1859)
484      iyr1  = nyear - 1859 + 1
485      iyr2  = iyr1 + 1
486      if (iyr1 .le. 1) then
487         !! before 1860
488         f_xco2a(:,:) = hist_pco2(1)
489      elseif (iyr2 .ge. 242) then
490         !! after 2099
491         f_xco2a(:,:) = hist_pco2(242)
492      else
493         !! just right
494         fq0 = hist_pco2(iyr1)
495         fq1 = hist_pco2(iyr2)
496         fq2 = real(nsec_day) / (60.0 * 60.0 * 24.0)
497         !! AXY (14/06/12): tweaked to make more sense (and be correct)
498#  if defined key_bs_axy_yrlen
499         fq3 = (real(nday_year) - 1.0 + fq2) / 360.0  !! bugfix: for 360d year with HadGEM2-ES forcing
500#  else
501         fq3 = (real(nday_year) - 1.0 + fq2) / 365.0  !! original use of 365 days (not accounting for leap year or 360d year)
502#  endif
503         fq4 = (fq0 * (1.0 - fq3)) + (fq1 * fq3)
504         f_xco2a(:,:) = fq4
505      endif
506#  if defined key_axy_pi_co2
507      f_xco2a(:,:) = 284.725          !! OCMIP pre-industrial pCO2
508#  endif
509      !! IF(lwp) WRITE(numout,*) ' MEDUSA nyear     =', nyear
510      !! IF(lwp) WRITE(numout,*) ' MEDUSA nsec_day  =', real(nsec_day)
511      !! IF(lwp) WRITE(numout,*) ' MEDUSA nday_year =', real(nday_year)
512      !! AXY (29/01/14): remove surplus diagnostics
513      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq0       =', fq0
514      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq1       =', fq1
515      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq2       =', fq2
516      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq3       =', fq3
517      IF(lwp) WRITE(numout,*) ' MEDUSA atm pCO2  =', f_xco2a(1,1)
518# endif
519
520# if defined key_debug_medusa
521      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for carbonate chemistry'
522      IF (lwp) write (numout,*) 'trc_bio_medusa: kt = ', kt
523      IF (lwp) write (numout,*) 'trc_bio_medusa: nittrc000 = ', nittrc000
524      CALL flush(numout)
525# endif 
526
527# if defined key_roam
528      !! AXY (20/11/14): alter to call on first MEDUSA timestep and then every
529      !!                 month (this is hardwired as 960 timesteps but should
530      !!                 be calculated and done properly
531      !! IF( kt == nit000 .or. mod(kt,1920) == 0 ) THEN
532      !! IF( kt == nittrc000 .or. mod(kt,960) == 0 ) THEN
533      !!=============================
534      !! Jpalm -- 07-10-2016 -- need to change carb-chem frequency call :
535      !!          we don't want to call on the first time-step of all run submission,
536      !!          but only on the very first time-step, and then every month
537      !!          So we call on nittrc000 if not restarted run,
538      !!          else if one month after last call.
539      !!          assume one month is 30d --> 3600*24*30 : 2592000s
540      !!          try to call carb-chem at 1st month's tm-stp : x * 30d + 1*rdt(i.e: mod = rdt)   
541      !!          ++ need to pass carb-chem output var through restarts
542      If ( ( kt == nittrc000 .AND. .NOT.ln_rsttr ) .OR. mod(kt*rdt,2592000.) == rdt ) THEN
543         !!----------------------------------------------------------------------
544         !! Calculate the carbonate chemistry for the whole ocean on the first
545         !! simulation timestep and every month subsequently; the resulting 3D
546         !! field of omega calcite is used to determine the depth of the CCD
547         !!----------------------------------------------------------------------
548         CALL carb_chem( kt )
549
550      ENDIF
551# endif
552
553# if defined key_debug_medusa
554      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for full domain calculations'
555      CALL flush(numout)
556# endif 
557
558      !!----------------------------------------------------------------------
559      !! MEDUSA has unified equation through the water column
560      !! (Diff. from LOBSTER which has two sets: bio- and non-bio layers)
561      !! Statement below in LOBSTER is different: DO jk = 1, jpkbm1         
562      !!----------------------------------------------------------------------
563      !!
564      !! NOTE: the ordering of the loops below differs from that of some other
565      !! models; looping over the vertical dimension is the outermost loop and
566      !! this complicates some calculations (e.g. storage of vertical fluxes
567      !! that can otherwise be done via a singular variable require 2D fields
568      !! here); however, these issues are relatively easily resolved, but the
569      !! loops CANNOT be reordered without potentially causing code efficiency
570      !! problems (e.g. array indexing means that reordering the loops would
571      !! require skipping between widely-spaced memory location; potentially
572      !! outside those immediately cached)
573      !!
574      !! OPEN vertical loop
575      DO jk = 1,jpk
576         !! OPEN horizontal loops
577         DO jj = 2,jpjm1
578         DO ji = 2,jpim1
579            !! OPEN wet point IF..THEN loop
580            if (tmask(ji,jj,jk).eq.1) then               
581               !!======================================================================
582               !! SETUP LOCAL GRID CELL
583               !!======================================================================
584               !!
585               !!---------------------------------------------------------------------
586               !! Some notes on grid vertical structure
587               !! - fsdepw(ji,jj,jk) is the depth of the upper surface of level jk
588               !! - fsde3w(ji,jj,jk) is *approximately* the midpoint of level jk
589               !! - fse3t(ji,jj,jk)  is the thickness of level jk
590               !!---------------------------------------------------------------------
591               !!
592               !! AXY (01/03/10): set up level depth (bottom of level)
593               fdep1(ji,jj) = fsdepw(ji,jj,jk) + fse3t(ji,jj,jk)
594               !! AXY (28/11/16): local seafloor depth
595               !!                 previously mbathy(ji,jj) - 1, now mbathy(ji,jj)
596               mbathy(ji,jj) = mbathy(ji,jj)
597               !!
598               !! set up model tracers
599               !! negative values of state variables are not allowed to
600               !! contribute to the calculated fluxes
601               zchn(ji,jj) = max(0.,trn(ji,jj,jk,jpchn)) !! non-diatom chlorophyll
602               zchd(ji,jj) = max(0.,trn(ji,jj,jk,jpchd)) !! diatom chlorophyll
603               zphn(ji,jj) = max(0.,trn(ji,jj,jk,jpphn)) !! non-diatoms
604               zphd(ji,jj) = max(0.,trn(ji,jj,jk,jpphd)) !! diatoms
605               zpds(ji,jj) = max(0.,trn(ji,jj,jk,jppds)) !! diatom silicon
606               !! AXY (28/01/10): probably need to take account of chl/biomass connection
607               if (zchn(ji,jj).eq.0.) zphn(ji,jj) = 0.
608               if (zchd(ji,jj).eq.0.) zphd(ji,jj) = 0.
609               if (zphn(ji,jj).eq.0.) zchn(ji,jj) = 0.
610               if (zphd(ji,jj).eq.0.) zchd(ji,jj) = 0.
611          !! AXY (23/01/14): duh - why did I forget diatom silicon?
612          if (zpds(ji,jj).eq.0.) zphd(ji,jj) = 0.
613          if (zphd(ji,jj).eq.0.) zpds(ji,jj) = 0.
614               zzmi(ji,jj) = max(0.,trn(ji,jj,jk,jpzmi)) !! microzooplankton
615               zzme(ji,jj) = max(0.,trn(ji,jj,jk,jpzme)) !! mesozooplankton
616               zdet(ji,jj) = max(0.,trn(ji,jj,jk,jpdet)) !! detrital nitrogen
617               zdin(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) !! dissolved inorganic nitrogen
618               zsil(ji,jj) = max(0.,trn(ji,jj,jk,jpsil)) !! dissolved silicic acid
619               zfer(ji,jj) = max(0.,trn(ji,jj,jk,jpfer)) !! dissolved "iron"
620# if defined key_roam
621               zdtc(ji,jj) = max(0.,trn(ji,jj,jk,jpdtc)) !! detrital carbon
622               zdic(ji,jj) = max(0.,trn(ji,jj,jk,jpdic)) !! dissolved inorganic carbon
623               zalk(ji,jj) = max(0.,trn(ji,jj,jk,jpalk)) !! alkalinity
624               zoxy(ji,jj) = max(0.,trn(ji,jj,jk,jpoxy)) !! oxygen
625#  if defined key_axy_carbchem && defined key_mocsy
626               zpho(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) / 16.0 !! phosphate via DIN and Redfield
627#  endif
628               !!
629               !! also need physical parameters for gas exchange calculations
630               ztmp(ji,jj) = tsn(ji,jj,jk,jp_tem)
631               zsal(ji,jj) = tsn(ji,jj,jk,jp_sal)
632               !!
633          !! AXY (28/02/14): check input fields
634               if (ztmp(ji,jj) .lt. -3.0 .or. ztmp(ji,jj) .gt. 40.0 ) then
635                  IF(lwp) WRITE(numout,*) ' trc_bio_medusa: T WARNING 2D, ', &
636                  tsb(ji,jj,jk,jp_tem), tsn(ji,jj,jk,jp_tem), ' at (',    &
637                  ji, ',', jj, ',', jk, ') at time', kt
638        IF(lwp) WRITE(numout,*) ' trc_bio_medusa: T SWITCHING 2D, ', &
639                  tsn(ji,jj,jk,jp_tem), ' -> ', tsb(ji,jj,jk,jp_tem)
640                  ztmp(ji,jj) = tsb(ji,jj,jk,jp_tem) !! temperature
641               endif
642               if (zsal(ji,jj) .lt. 0.0 .or. zsal(ji,jj) .gt. 45.0 ) then
643                  IF(lwp) WRITE(numout,*) ' trc_bio_medusa: S WARNING 2D, ', &
644                  tsb(ji,jj,jk,jp_sal), tsn(ji,jj,jk,jp_sal), ' at (',    &
645                  ji, ',', jj, ',', jk, ') at time', kt
646               endif
647# else
648               zdtc(ji,jj) = zdet(ji,jj) * xthetad              !! implicit detrital carbon
649# endif
650# if defined key_debug_medusa
651               if (idf.eq.1) then
652               !! AXY (15/01/10)
653                  if (trn(ji,jj,jk,jpdin).lt.0.) then
654                     IF (lwp) write (numout,*) '------------------------------'
655                     IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR =', trn(ji,jj,jk,jpdin)
656                     IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR @', ji, jj, jk, kt
657                  endif
658                  if (trn(ji,jj,jk,jpsil).lt.0.) then
659                     IF (lwp) write (numout,*) '------------------------------'
660                     IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR =', trn(ji,jj,jk,jpsil)
661                     IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR @', ji, jj, jk, kt
662                  endif
663#  if defined key_roam
664                  if (trn(ji,jj,jk,jpdic).lt.0.) then
665                     IF (lwp) write (numout,*) '------------------------------'
666                     IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR =', trn(ji,jj,jk,jpdic)
667                     IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR @', ji, jj, jk, kt
668                  endif
669                  if (trn(ji,jj,jk,jpalk).lt.0.) then
670                     IF (lwp) write (numout,*) '------------------------------'
671                     IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR =', trn(ji,jj,jk,jpalk)
672                     IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR @', ji, jj, jk, kt
673                  endif
674                  if (trn(ji,jj,jk,jpoxy).lt.0.) then
675                     IF (lwp) write (numout,*) '------------------------------'
676                     IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR =', trn(ji,jj,jk,jpoxy)
677                     IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR @', ji, jj, jk, kt
678                  endif
679#  endif
680               endif
681# endif
682# if defined key_debug_medusa
683               !! report state variable values
684               if (idf.eq.1.AND.idfval.eq.1) then
685                  IF (lwp) write (numout,*) '------------------------------'
686                  IF (lwp) write (numout,*) 'fthk(',jk,') = ', fse3t(ji,jj,jk)
687                  IF (lwp) write (numout,*) 'zphn(',jk,') = ', zphn(ji,jj)
688                  IF (lwp) write (numout,*) 'zphd(',jk,') = ', zphd(ji,jj)
689                  IF (lwp) write (numout,*) 'zpds(',jk,') = ', zpds(ji,jj)
690                  IF (lwp) write (numout,*) 'zzmi(',jk,') = ', zzmi(ji,jj)
691                  IF (lwp) write (numout,*) 'zzme(',jk,') = ', zzme(ji,jj)
692                  IF (lwp) write (numout,*) 'zdet(',jk,') = ', zdet(ji,jj)
693                  IF (lwp) write (numout,*) 'zdin(',jk,') = ', zdin(ji,jj)
694                  IF (lwp) write (numout,*) 'zsil(',jk,') = ', zsil(ji,jj)
695                  IF (lwp) write (numout,*) 'zfer(',jk,') = ', zfer(ji,jj)
696#  if defined key_roam
697                  IF (lwp) write (numout,*) 'zdtc(',jk,') = ', zdtc(ji,jj)
698                  IF (lwp) write (numout,*) 'zdic(',jk,') = ', zdic(ji,jj)
699                  IF (lwp) write (numout,*) 'zalk(',jk,') = ', zalk(ji,jj)
700                  IF (lwp) write (numout,*) 'zoxy(',jk,') = ', zoxy(ji,jj)                 
701#  endif
702               endif
703# endif
704
705# if defined key_debug_medusa
706               if (idf.eq.1.AND.idfval.eq.1.AND.jk.eq.1) then
707                  IF (lwp) write (numout,*) '------------------------------'
708                  IF (lwp) write (numout,*) 'dust      = ', dust(ji,jj)
709               endif
710# endif
711
712               !! sum tracers for inventory checks
713               IF( lk_iomput ) THEN
714                  IF ( med_diag%INVTN%dgsave )   THEN
715                     ftot_n(ji,jj)  = ftot_n(ji,jj) + &
716                             (fse3t(ji,jj,jk) * ( zphn(ji,jj) + zphd(ji,jj) + zzmi(ji,jj) + zzme(ji,jj) + zdet(ji,jj) + zdin(ji,jj) ) )
717                  ENDIF
718                  IF ( med_diag%INVTSI%dgsave )  THEN
719                     ftot_si(ji,jj) = ftot_si(ji,jj) + & 
720                             (fse3t(ji,jj,jk) * ( zpds(ji,jj) + zsil(ji,jj) ) )
721                  ENDIF
722                  IF ( med_diag%INVTFE%dgsave )  THEN
723                     ftot_fe(ji,jj) = ftot_fe(ji,jj) + & 
724                             (fse3t(ji,jj,jk) * ( xrfn * ( zphn(ji,jj) + zphd(ji,jj) + zzmi(ji,jj) + zzme(ji,jj) + zdet(ji,jj) ) + zfer(ji,jj) ) )
725                  ENDIF
726# if defined key_roam
727                  IF ( med_diag%INVTC%dgsave )  THEN
728                     ftot_c(ji,jj)  = ftot_c(ji,jj) + & 
729                             (fse3t(ji,jj,jk) * ( (xthetapn * zphn(ji,jj)) + (xthetapd * zphd(ji,jj)) + &
730                             (xthetazmi * zzmi(ji,jj)) + (xthetazme * zzme(ji,jj)) + zdtc(ji,jj) +   &
731                             zdic(ji,jj) ) )
732                  ENDIF
733                  IF ( med_diag%INVTALK%dgsave ) THEN
734                     ftot_a(ji,jj)  = ftot_a(ji,jj) + (fse3t(ji,jj,jk) * ( zalk(ji,jj) ) )
735                  ENDIF
736                  IF ( med_diag%INVTO2%dgsave )  THEN
737                     ftot_o2(ji,jj) = ftot_o2(ji,jj) + (fse3t(ji,jj,jk) * ( zoxy(ji,jj) ) )
738                  ENDIF
739                  !!
740                  !! AXY (10/11/16): CMIP6 diagnostics
741                  IF ( med_diag%INTDISSIC%dgsave ) THEN
742                     intdissic(ji,jj) = intdissic(ji,jj) + (fse3t(ji,jj,jk) * zdic(ji,jj))
743                  ENDIF
744                  IF ( med_diag%INTDISSIN%dgsave ) THEN
745                     intdissin(ji,jj) = intdissin(ji,jj) + (fse3t(ji,jj,jk) * zdin(ji,jj))
746                  ENDIF
747                  IF ( med_diag%INTDISSISI%dgsave ) THEN
748                     intdissisi(ji,jj) = intdissisi(ji,jj) + (fse3t(ji,jj,jk) * zsil(ji,jj))
749                  ENDIF
750                  IF ( med_diag%INTTALK%dgsave ) THEN
751                     inttalk(ji,jj) = inttalk(ji,jj) + (fse3t(ji,jj,jk) * zalk(ji,jj))
752                  ENDIF
753                  IF ( med_diag%O2min%dgsave ) THEN
754                     if ( zoxy(ji,jj) < o2min(ji,jj) ) then
755                        o2min(ji,jj)  = zoxy(ji,jj)
756                        IF ( med_diag%ZO2min%dgsave ) THEN
757                           zo2min(ji,jj) = (fsdepw(ji,jj,jk) + fdep1(ji,jj)) / 2. !! layer midpoint
758                        ENDIF
759                     endif
760                  ENDIF
761# endif
762               ENDIF
763
764               CALL flush(numout)
765
766               !!======================================================================
767               !! LOCAL GRID CELL CALCULATIONS
768               !!======================================================================
769               !!
770# if defined key_roam
771               if ( jk .eq. 1 ) then
772                  !!----------------------------------------------------------------------
773                  !! Air-sea gas exchange
774                  !!----------------------------------------------------------------------
775                  IF (lk_oasis) THEN
776                     f_xco2a(ji,jj) = PCO2a_in_cpl(ji,jj)        !! use 2D atm xCO2 from atm coupling
777                  ENDIF
778                  !!
779                  !! AXY (23/06/15): as part of an effort to update the carbonate chemistry
780                  !!                 in MEDUSA, the gas transfer velocity used in the carbon
781                  !!                 and oxygen cycles has been harmonised and is calculated
782                  !!                 by the same function here; this harmonisation includes
783                  !!                 changes to the PML carbonate chemistry scheme so that
784                  !!                 it too makes use of the same gas transfer velocity; the
785                  !!                 preferred parameterisation of this is Wanninkhof (2014),
786                  !!                 option 7
787                  !!
788#   if defined key_debug_medusa
789                     IF (lwp) write (numout,*) 'trc_bio_medusa: entering gas_transfer'
790                     CALL flush(numout)
791#   endif
792                  CALL gas_transfer( wndm(ji,jj), 1, 7, &  ! inputs
793                                     f_kw660(ji,jj) )        ! outputs
794#   if defined key_debug_medusa
795                     IF (lwp) write (numout,*) 'trc_bio_medusa: exiting gas_transfer'
796                     CALL flush(numout)
797#   endif
798                  !!
799                  !! air pressure (atm); ultimately this will use air pressure at the base
800                  !! of the UKESM1 atmosphere
801                  !!                                     
802                  f_pp0(ji,jj)   = 1.0
803                  !!
804                  !! IF(lwp) WRITE(numout,*) ' MEDUSA ztmp    =', ztmp(ji,jj)
805                  !! IF(lwp) WRITE(numout,*) ' MEDUSA zwind_i =', zwind_i(ji,jj)
806                  !! IF(lwp) WRITE(numout,*) ' MEDUSA zwind_j =', zwind_j(ji,jj)
807                  !! IF(lwp) WRITE(numout,*) ' MEDUSA wndm    =', wndm(ji,jj)
808                  !! IF(lwp) WRITE(numout,*) ' MEDUSA fr_i    =', fr_i(ji,jj)
809                  !!
810#  if defined key_axy_carbchem
811#   if defined key_mocsy
812                  !!
813                  !! AXY (22/06/15): use Orr & Epitalon (2015) MOCSY-2 carbonate
814                  !!                 chemistry package; note that depth is set to
815                  !!                 zero in this call
816                  CALL mocsy_interface( ztmp(ji,jj), zsal(ji,jj), zalk(ji,jj), zdic(ji,jj), zsil(ji,jj), zpho(ji,jj),        &  ! inputs
817                  f_pp0(ji,jj), 0.0, gphit(ji,jj), f_kw660(ji,jj), f_xco2a(ji,jj), 1,                   &  ! inputs
818                  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
819                  f_omcal(ji,jj), f_BetaD(ji,jj), f_rhosw(ji,jj), f_opres(ji,jj), f_insitut(ji,jj),            &  ! outputs
820                  f_pco2atm(ji,jj), f_fco2atm(ji,jj), f_schmidtco2(ji,jj), f_kwco2(ji,jj), f_K0(ji,jj),               &  ! outputs
821                  f_co2starair(ji,jj), f_co2flux(ji,jj), f_dpco2(ji,jj) )                                  ! outputs
822                  !!
823                  f_TDIC(ji,jj) = (zdic(ji,jj) / f_rhosw(ji,jj)) * 1000. ! mmol / m3 -> umol / kg
824                  f_TALK(ji,jj) = (zalk(ji,jj) / f_rhosw(ji,jj)) * 1000. !  meq / m3 ->  ueq / kg
825                  f_dcf(ji,jj)  = f_rhosw(ji,jj)
826#   else                 
827                  iters(ji,jj) = 0
828                  !!
829                  !! carbon dioxide (CO2); Jerry Blackford code (ostensibly OCMIP-2, but not)
830                  CALL trc_co2_medusa( ztmp(ji,jj), zsal(ji,jj), zdic(ji,jj), zalk(ji,jj), 0.0, f_kw660(ji,jj), f_xco2a(ji,jj),  &  ! inputs
831                  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
832                  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
833                  !!
834                  !! AXY (09/01/14): removed iteration and NaN checks; these have
835                  !!                 been moved to trc_co2_medusa together with a
836                  !!                 fudge that amends erroneous values (this is
837                  !!                 intended to be a temporary fudge!); the
838                  !!                 output warnings are retained here so that
839                  !!                 failure position can be determined
840                  if (iters(ji,jj) .eq. 25) then
841                     IF(lwp) WRITE(numout,*) ' trc_bio_medusa: ITERS WARNING, ', &
842                     iters(ji,jj), ' AT (', ji, ', ', jj, ', ', jk, ') AT ', kt
843                  endif
844#   endif
845#  else
846                  !! AXY (18/04/13): switch off carbonate chemistry calculations; provide
847                  !!                 quasi-sensible alternatives
848                  f_ph(ji,jj)           = 8.1
849                  f_pco2w(ji,jj)        = f_xco2a(ji,jj)
850                  f_h2co3(ji,jj)        = 0.005 * zdic(ji,jj)
851                  f_hco3(ji,jj)         = 0.865 * zdic(ji,jj)
852                  f_co3(ji,jj)          = 0.130 * zdic(ji,jj)
853                  f_omcal(ji,jj) = 4.
854                  f_omarg(ji,jj) = 2.
855                  f_co2flux(ji,jj)      = 0.
856                  f_TDIC(ji,jj)         = zdic(ji,jj)
857                  f_TALK(ji,jj)         = zalk(ji,jj)
858                  f_dcf(ji,jj)          = 1.026
859                  f_henry(ji,jj)        = 1.
860                  !! AXY (23/06/15): add in some extra MOCSY diagnostics
861                  f_fco2w(ji,jj)        = f_xco2a(ji,jj)
862                  f_BetaD(ji,jj)        = 1.
863                  f_rhosw(ji,jj)        = 1.026
864                  f_opres(ji,jj)        = 0.
865                  f_insitut(ji,jj)      = ztmp(ji,jj)
866                  f_pco2atm(ji,jj)      = f_xco2a(ji,jj)
867                  f_fco2atm(ji,jj)      = f_xco2a(ji,jj)
868                  f_schmidtco2(ji,jj)   = 660.
869                  f_kwco2(ji,jj)        = 0.
870                  f_K0(ji,jj)           = 0.
871                  f_co2starair(ji,jj)   = f_xco2a(ji,jj)
872                  f_dpco2(ji,jj)        = 0.
873#  endif
874                  !!
875                  !! mmol/m2/s -> mmol/m3/d; correct for sea-ice; divide through by layer thickness
876                  f_co2flux(ji,jj) = (1. - fr_i(ji,jj)) * f_co2flux(ji,jj) * 86400. / fse3t(ji,jj,jk)
877                  !!
878                  !! oxygen (O2); OCMIP-2 code
879                  !! AXY (23/06/15): amend input list for oxygen to account for common gas
880                  !!                 transfer velocity
881                  !! Note that f_kwo2 is an about from the subroutine below,
882                  !! which doesn't seem to be used - marc 10/4/17
883                  CALL trc_oxy_medusa( ztmp(ji,jj), zsal(ji,jj), f_kw660(ji,jj), f_pp0(ji,jj), zoxy(ji,jj),  &  ! inputs
884                  f_kwo2(ji,jj), f_o2flux(ji,jj), f_o2sat(ji,jj) )                                ! outputs
885                  !!
886                  !! mmol/m2/s -> mol/m3/d; correct for sea-ice; divide through by layer thickness
887                  f_o2flux(ji,jj)  = (1. - fr_i(ji,jj)) * f_o2flux(ji,jj) * 86400. / fse3t(ji,jj,jk)
888                  !!
889                  !! Jpalm (08-2014)
890                  !! DMS surface concentration calculation
891                  !! initialy added for UKESM1 model.
892                  !! using MET-OFFICE subroutine.
893                  !! DMS module only needs Chl concentration and MLD
894                  !! to get an aproximate value of DMS concentration.
895                  !! air-sea fluxes are calculated by atmospheric chemitry model
896                  !! from atm and oc-surface concentrations.
897                  !!
898                  !! AXY (13/03/15): this is amended to calculate all of the DMS
899                  !!                 estimates examined during UKESM1 (see comments
900                  !!                 in trcdms_medusa.F90)
901                  !!
902                  IF (jdms .eq. 1) THEN
903                     !!
904                     !! feed in correct inputs
905                     if (jdms_input .eq. 0) then
906                        !! use instantaneous inputs
907                        CALL trc_dms_medusa( zchn(ji,jj), zchd(ji,jj), hmld(ji,jj), qsr(ji,jj), zdin(ji,jj), &  ! inputs
908                        dms_andr(ji,jj), dms_simo(ji,jj), dms_aran(ji,jj), dms_hall(ji,jj) )                           ! outputs
909                     else
910                        !! use diel-average inputs
911                        CALL trc_dms_medusa( zn_dms_chn(ji,jj), zn_dms_chd(ji,jj), &  ! inputs
912                        zn_dms_mld(ji,jj), zn_dms_qsr(ji,jj), zn_dms_din(ji,jj),   &  ! inputs
913                        dms_andr(ji,jj), dms_simo(ji,jj), dms_aran(ji,jj), dms_hall(ji,jj) )                      ! outputs
914                     endif
915                     !!
916                     !! assign correct output to variable passed to atmosphere
917                     if     (jdms_model .eq. 1) then
918                        dms_surf(ji,jj) = dms_andr(ji,jj)
919                     elseif (jdms_model .eq. 2) then
920                        dms_surf(ji,jj) = dms_simo(ji,jj)
921                     elseif (jdms_model .eq. 3) then
922                        dms_surf(ji,jj) = dms_aran(ji,jj)
923                     elseif (jdms_model .eq. 4) then
924                        dms_surf(ji,jj) = dms_hall(ji,jj)
925                     endif
926                     !!
927                     !! 2D diag through iom_use
928                     IF( lk_iomput ) THEN
929                       IF( med_diag%DMS_SURF%dgsave ) THEN
930                         dms_surf2d(ji,jj) = dms_surf(ji,jj)
931                       ENDIF
932                       IF( med_diag%DMS_ANDR%dgsave ) THEN
933                         dms_andr2d(ji,jj) = dms_andr(ji,jj)
934                       ENDIF
935                       IF( med_diag%DMS_SIMO%dgsave ) THEN
936                         dms_simo2d(ji,jj) = dms_simo(ji,jj)
937                       ENDIF
938                       IF( med_diag%DMS_ARAN%dgsave ) THEN
939                         dms_aran2d(ji,jj) = dms_aran(ji,jj)
940                       ENDIF
941                       IF( med_diag%DMS_HALL%dgsave ) THEN
942                         dms_hall2d(ji,jj) = dms_hall(ji,jj)
943                       ENDIF
944#   if defined key_debug_medusa
945                       IF (lwp) write (numout,*) 'trc_bio_medusa: finish calculating dms'
946                     CALL flush(numout)
947#   endif
948                     ENDIF
949                     !! End iom
950                  ENDIF
951                  !! End DMS Loop
952                  !!
953                  !! store 2D outputs
954                  !!
955                  !! JPALM -- 17-11-16 -- put fgco2 out of diag request
956                  !!                    is needed for coupling; pass through restart
957                  !! IF( med_diag%FGCO2%dgsave ) THEN
958                     !! convert from  mol/m2/day to kg/m2/s
959                     fgco2(ji,jj) = f_co2flux(ji,jj) * fse3t(ji,jj,jk) * CO2flux_conv  !! mmol-C/m3/d -> kg-CO2/m2/s
960                  !! ENDIF
961                  IF ( lk_iomput ) THEN
962                      IF( med_diag%ATM_PCO2%dgsave ) THEN
963                         f_pco2a2d(ji,jj) = f_pco2atm(ji,jj)
964                      ENDIF
965                      IF( med_diag%OCN_PCO2%dgsave ) THEN
966                         f_pco2w2d(ji,jj) = f_pco2w(ji,jj)
967                      ENDIF
968                      IF( med_diag%CO2FLUX%dgsave ) THEN
969                         f_co2flux2d(ji,jj) = f_co2flux(ji,jj) * fse3t(ji,jj,jk)           !! mmol/m3/d -> mmol/m2/d
970                      ENDIF
971                      IF( med_diag%TCO2%dgsave ) THEN
972                         f_TDIC2d(ji,jj) = f_TDIC(ji,jj)
973                      ENDIF
974                      IF( med_diag%TALK%dgsave ) THEN
975                         f_TALK2d(ji,jj) = f_TALK(ji,jj)
976                      ENDIF
977                      IF( med_diag%KW660%dgsave ) THEN
978                         f_kw6602d(ji,jj) = f_kw660(ji,jj)
979                      ENDIF
980                      IF( med_diag%ATM_PP0%dgsave ) THEN
981                         f_pp02d(ji,jj) = f_pp0(ji,jj)
982                      ENDIF
983                      IF( med_diag%O2FLUX%dgsave ) THEN
984                         f_o2flux2d(ji,jj) = f_o2flux(ji,jj)
985                      ENDIF
986                      IF( med_diag%O2SAT%dgsave ) THEN
987                         f_o2sat2d(ji,jj) = f_o2sat(ji,jj)
988                      ENDIF
989                      !! AXY (24/11/16): add in extra MOCSY diagnostics
990                      IF( med_diag%ATM_XCO2%dgsave ) THEN
991                         f_xco2a_2d(ji,jj) = f_xco2a(ji,jj)
992                      ENDIF
993                      IF( med_diag%OCN_FCO2%dgsave ) THEN
994                         f_fco2w_2d(ji,jj) = f_fco2w(ji,jj)
995                      ENDIF
996                      IF( med_diag%ATM_FCO2%dgsave ) THEN
997                         f_fco2a_2d(ji,jj) = f_fco2atm(ji,jj)
998                      ENDIF
999                      IF( med_diag%OCN_RHOSW%dgsave ) THEN
1000                         f_ocnrhosw_2d(ji,jj) = f_rhosw(ji,jj)
1001                      ENDIF
1002                      IF( med_diag%OCN_SCHCO2%dgsave ) THEN
1003                         f_ocnschco2_2d(ji,jj) = f_schmidtco2(ji,jj)
1004                      ENDIF
1005                      IF( med_diag%OCN_KWCO2%dgsave ) THEN
1006                         f_ocnkwco2_2d(ji,jj) = f_kwco2(ji,jj)
1007                      ENDIF
1008                      IF( med_diag%OCN_K0%dgsave ) THEN
1009                         f_ocnk0_2d(ji,jj) = f_K0(ji,jj)
1010                      ENDIF
1011                      IF( med_diag%CO2STARAIR%dgsave ) THEN
1012                         f_co2starair_2d(ji,jj) = f_co2starair(ji,jj)
1013                      ENDIF
1014                      IF( med_diag%OCN_DPCO2%dgsave ) THEN
1015                         f_ocndpco2_2d(ji,jj) = f_dpco2(ji,jj)
1016                      ENDIF
1017                  ENDIF
1018                  !!
1019               endif
1020               !! End jk = 1 loop within ROAM key
1021
1022               !! AXY (11/11/16): CMIP6 oxygen saturation 3D diagnostic
1023               IF ( med_diag%O2SAT3%dgsave ) THEN
1024                  call oxy_sato( ztmp(ji,jj), zsal(ji,jj), f_o2sat3 )
1025                  o2sat3(ji, jj, jk) = f_o2sat3
1026               ENDIF
1027
1028# endif
1029
1030               if ( jk .eq. 1 ) then
1031                  !!----------------------------------------------------------------------
1032                  !! River inputs
1033                  !!----------------------------------------------------------------------
1034                  !!
1035                  !! runoff comes in as        kg / m2 / s
1036                  !! used and written out as   m3 / m2 / d (= m / d)
1037                  !! where                     1000 kg / m2 / d = 1 m3 / m2 / d = 1 m / d
1038                  !!
1039                  !! AXY (17/07/14): the compiler doesn't like this line for some reason;
1040                  !!                 as MEDUSA doesn't even use runoff for riverine inputs,
1041                  !!                 a temporary solution is to switch off runoff entirely
1042                  !!                 here; again, this change is one of several that will
1043                  !!                 need revisiting once MEDUSA has bedded down in UKESM1;
1044                  !!                 particularly so if the land scheme provides information
1045                  !!                 concerning nutrient fluxes
1046                  !!
1047                  !! f_runoff(ji,jj) = sf_rnf(1)%fnow(ji,jj,1) / 1000. * 60. * 60. * 24.
1048                  f_runoff(ji,jj) = 0.0
1049                  !!
1050                  !! nutrients are added via rivers to the model in one of two ways:
1051                  !!   1. via river concentration; i.e. the average nutrient concentration
1052                  !!      of a river water is described by a spatial file, and this is
1053                  !!      multiplied by runoff to give a nutrient flux
1054                  !!   2. via direct river flux; i.e. the average nutrient flux due to
1055                  !!      rivers is described by a spatial file, and this is simply applied
1056                  !!      as a direct nutrient flux (i.e. it does not relate or respond to
1057                  !!      model runoff)
1058                  !! nutrient fields are derived from the GlobalNEWS 2 database; carbon and
1059                  !! alkalinity are derived from continent-scale DIC estimates (Huang et al.,
1060                  !! 2012) and some Arctic river alkalinity estimates (Katya?)
1061                  !!
1062                  !! as of 19/07/12, riverine nutrients can now be spread vertically across
1063                  !! several grid cells rather than just poured into the surface box; this
1064                  !! block of code is still executed, however, to set up the total amounts
1065                  !! of nutrient entering via rivers
1066                  !!
1067                  !! nitrogen
1068                  if (jriver_n .eq. 1) then
1069                     !! river concentration specified; use runoff to calculate input
1070                     f_riv_n(ji,jj) = f_runoff(ji,jj) * riv_n(ji,jj)
1071                  elseif (jriver_n .eq. 2) then
1072                     !! river flux specified; independent of runoff
1073                     f_riv_n(ji,jj) = riv_n(ji,jj)
1074                  endif
1075                  !!
1076                  !! silicon
1077                  if (jriver_si .eq. 1) then
1078                     !! river concentration specified; use runoff to calculate input
1079                     f_riv_si(ji,jj) = f_runoff(ji,jj) * riv_si(ji,jj)
1080                  elseif (jriver_si .eq. 2) then
1081                     !! river flux specified; independent of runoff
1082                     f_riv_si(ji,jj) = riv_si(ji,jj)
1083                  endif
1084                  !!
1085                  !! carbon
1086                  if (jriver_c .eq. 1) then
1087                     !! river concentration specified; use runoff to calculate input
1088                     f_riv_c(ji,jj) = f_runoff(ji,jj) * riv_c(ji,jj)
1089                  elseif (jriver_c .eq. 2) then
1090                     !! river flux specified; independent of runoff
1091                     f_riv_c(ji,jj) = riv_c(ji,jj)
1092                  endif
1093                  !!
1094                  !! alkalinity
1095                  if (jriver_alk .eq. 1) then
1096                     !! river concentration specified; use runoff to calculate input
1097                     f_riv_alk(ji,jj) = f_runoff(ji,jj) * riv_alk(ji,jj)
1098                  elseif (jriver_alk .eq. 2) then
1099                     !! river flux specified; independent of runoff
1100                     f_riv_alk(ji,jj) = riv_alk(ji,jj)
1101                  endif
1102
1103               endif
1104
1105               !!----------------------------------------------------------------------
1106               !! Chlorophyll calculations
1107               !!----------------------------------------------------------------------
1108               !!
1109               !! non-diatoms
1110          if (zphn(ji,jj).GT.rsmall) then
1111                  fthetan(ji,jj) = max(tiny(zchn(ji,jj)), (zchn(ji,jj) * xxi) / (zphn(ji,jj) + tiny(zphn(ji,jj))))
1112                  faln(ji,jj)    = xaln * fthetan(ji,jj)
1113               else
1114                  fthetan(ji,jj) = 0.
1115                  faln(ji,jj)    = 0.
1116               endif
1117               !!
1118               !! diatoms
1119          if (zphd(ji,jj).GT.rsmall) then
1120                  fthetad(ji,jj) = max(tiny(zchd(ji,jj)), (zchd(ji,jj) * xxi) / (zphd(ji,jj) + tiny(zphd(ji,jj))))
1121                  fald(ji,jj)    = xald * fthetad(ji,jj)
1122               else
1123                  fthetad(ji,jj) = 0.
1124                  fald(ji,jj)    = 0.
1125               endif
1126
1127# if defined key_debug_medusa
1128               !! report biological calculations
1129               if (idf.eq.1.AND.idfval.eq.1) then
1130                  IF (lwp) write (numout,*) '------------------------------'
1131                  IF (lwp) write (numout,*) 'faln(',jk,') = ', faln(ji,jj)
1132                  IF (lwp) write (numout,*) 'fald(',jk,') = ', fald(ji,jj)
1133               endif
1134# endif
1135
1136               !!----------------------------------------------------------------------
1137               !! Phytoplankton light limitation
1138               !!----------------------------------------------------------------------
1139               !!
1140               !! It is assumed xpar is the depth-averaged (vertical layer) PAR
1141               !! Light limitation (check self-shading) in W/m2
1142               !!
1143               !! Note that there is no temperature dependence in phytoplankton
1144               !! growth rate or any other function.
1145               !! In calculation of Chl/Phy ratio tiny(phyto) is introduced to avoid
1146               !! NaNs in case of Phy==0. 
1147               !!
1148               !! fthetad and fthetan are Chl:C ratio (gChl/gC) in diat and non-diat:
1149               !! for 1:1 Chl:P ratio (mgChl/mmolN) theta=0.012
1150               !!
1151               !! AXY (16/07/09)
1152               !! temperature for new Eppley style phytoplankton growth
1153               fun_T(ji,jj)   = 1.066**(1.0 * tsn(ji,jj,jk,jp_tem))
1154               !! AXY (16/05/11): add in new Q10 (1.5, not 2.0) for
1155               !phytoplankton
1156               !!                 growth; remin. unaffected
1157               fun_Q10(ji,jj) = jq10**((tsn(ji,jj,jk,jp_tem) - 0.0) / 10.0)
1158               if (jphy.eq.1) then
1159                  xvpnT(ji,jj) = xvpn * fun_T(ji,jj)
1160                  xvpdT(ji,jj) = xvpd * fun_T(ji,jj)
1161               elseif (jphy.eq.2) then
1162                  xvpnT(ji,jj) = xvpn * fun_Q10(ji,jj)
1163                  xvpdT(ji,jj) = xvpd * fun_Q10(ji,jj)
1164               else
1165                  xvpnT(ji,jj) = xvpn
1166                  xvpdT(ji,jj) = xvpd
1167               endif
1168               !!
1169               !! non-diatoms
1170               fchn1(ji,jj)   = (xvpnT(ji,jj) * xvpnT(ji,jj)) + (faln(ji,jj) * faln(ji,jj) * xpar(ji,jj,jk) * xpar(ji,jj,jk))
1171               if (fchn1(ji,jj).GT.rsmall) then
1172                  fchn(ji,jj)    = xvpnT(ji,jj) / (sqrt(fchn1(ji,jj)) + tiny(fchn1(ji,jj)))
1173               else
1174                  fchn(ji,jj)    = 0.
1175               endif
1176               fjln(ji,jj)    = fchn(ji,jj) * faln(ji,jj) * xpar(ji,jj,jk) !! non-diatom J term
1177               fjlim_pn(ji,jj) = fjln(ji,jj) / xvpnT(ji,jj)
1178               !!
1179               !! diatoms
1180               fchd1(ji,jj)   = (xvpdT(ji,jj) * xvpdT(ji,jj)) + (fald(ji,jj) * fald(ji,jj) * xpar(ji,jj,jk) * xpar(ji,jj,jk))
1181               if (fchd1(ji,jj).GT.rsmall) then
1182                  fchd(ji,jj)    = xvpdT(ji,jj) / (sqrt(fchd1(ji,jj)) + tiny(fchd1(ji,jj)))
1183               else
1184                  fchd(ji,jj)    = 0.
1185               endif
1186               fjld(ji,jj)    = fchd(ji,jj) * fald(ji,jj) * xpar(ji,jj,jk) !! diatom J term
1187               fjlim_pd(ji,jj) = fjld(ji,jj) / xvpdT(ji,jj)
1188     
1189# if defined key_debug_medusa
1190               !! report phytoplankton light limitation
1191               if (idf.eq.1.AND.idfval.eq.1) then
1192                  IF (lwp) write (numout,*) '------------------------------'
1193                  IF (lwp) write (numout,*) 'fchn(',jk,') = ', fchn(ji,jj)
1194                  IF (lwp) write (numout,*) 'fchd(',jk,') = ', fchd(ji,jj)
1195                  IF (lwp) write (numout,*) 'fjln(',jk,') = ', fjln(ji,jj)
1196                  IF (lwp) write (numout,*) 'fjld(',jk,') = ', fjld(ji,jj)
1197               endif
1198# endif
1199
1200               !!----------------------------------------------------------------------
1201               !! Phytoplankton nutrient limitation
1202               !!----------------------------------------------------------------------
1203               !!
1204               !! non-diatoms (N, Fe)
1205               fnln(ji,jj) = zdin(ji,jj) / (zdin(ji,jj) + xnln) !! non-diatom Qn term
1206               ffln(ji,jj) = zfer(ji,jj) / (zfer(ji,jj) + xfln) !! non-diatom Qf term
1207               !!
1208               !! diatoms (N, Si, Fe)
1209               fnld(ji,jj) = zdin(ji,jj) / (zdin(ji,jj) + xnld) !! diatom Qn term
1210               fsld(ji,jj) = zsil(ji,jj) / (zsil(ji,jj) + xsld) !! diatom Qs term
1211               ffld(ji,jj) = zfer(ji,jj) / (zfer(ji,jj) + xfld) !! diatom Qf term
1212
1213# if defined key_debug_medusa
1214               !! report phytoplankton nutrient limitation
1215               if (idf.eq.1.AND.idfval.eq.1) then
1216                  IF (lwp) write (numout,*) '------------------------------'
1217                  IF (lwp) write (numout,*) 'fnln(',jk,') = ', fnln(ji,jj)
1218                  IF (lwp) write (numout,*) 'fnld(',jk,') = ', fnld(ji,jj)
1219                  IF (lwp) write (numout,*) 'ffln(',jk,') = ', ffln(ji,jj)
1220                  IF (lwp) write (numout,*) 'ffld(',jk,') = ', ffld(ji,jj)
1221                  IF (lwp) write (numout,*) 'fsld(',jk,') = ', fsld(ji,jj)
1222               endif
1223# endif
1224
1225               !!----------------------------------------------------------------------
1226               !! Primary production (non-diatoms)
1227               !! (note: still needs multiplying by phytoplankton concentration)
1228               !!----------------------------------------------------------------------
1229               !!
1230               if (jliebig .eq. 0) then
1231                  !! multiplicative nutrient limitation
1232                  fpnlim(ji,jj) = fnln(ji,jj) * ffln(ji,jj)
1233               elseif (jliebig .eq. 1) then
1234                  !! Liebig Law (= most limiting) nutrient limitation
1235                  fpnlim(ji,jj) = min(fnln(ji,jj), ffln(ji,jj))
1236               endif
1237               fprn(ji,jj) = fjln(ji,jj) * fpnlim(ji,jj)
1238
1239               !!----------------------------------------------------------------------
1240               !! Primary production (diatoms)
1241               !! (note: still needs multiplying by phytoplankton concentration)
1242               !!
1243               !! production here is split between nitrogen production and that of
1244               !! silicon; depending upon the "intracellular" ratio of Si:N, model
1245               !! diatoms will uptake nitrogen/silicon differentially; this borrows
1246               !! from the diatom model of Mongin et al. (2006)
1247               !!----------------------------------------------------------------------
1248               !!
1249               if (jliebig .eq. 0) then
1250                  !! multiplicative nutrient limitation
1251                  fpdlim(ji,jj) = fnld(ji,jj) * ffld(ji,jj)
1252               elseif (jliebig .eq. 1) then
1253                  !! Liebig Law (= most limiting) nutrient limitation
1254                  fpdlim(ji,jj) = min(fnld(ji,jj), ffld(ji,jj))
1255               endif
1256               !!
1257          if (zphd(ji,jj).GT.rsmall .AND. zpds(ji,jj).GT.rsmall) then
1258                  !! "intracellular" elemental ratios
1259                  ! fsin(ji,jj)  = zpds(ji,jj) / (zphd(ji,jj) + tiny(zphd(ji,jj)))
1260                  ! fnsi(ji,jj)  = zphd(ji,jj) / (zpds(ji,jj) + tiny(zpds(ji,jj)))
1261                  fsin(ji,jj) = 0.0
1262                  IF( zphd(ji,jj) .GT. rsmall) fsin(ji,jj)  = zpds(ji,jj) / zphd(ji,jj)
1263                  fnsi(ji,jj) = 0.0
1264                  IF( zpds(ji,jj) .GT. rsmall) fnsi(ji,jj)  = zphd(ji,jj) / zpds(ji,jj)
1265                  !! AXY (23/02/10): these next variables derive from Mongin et al. (2003)
1266                  fsin1 = 3.0 * xsin0 !! = 0.6
1267                  fnsi1 = 1.0 / fsin1 !! = 1.667
1268                  fnsi2 = 1.0 / xsin0 !! = 5.0
1269                  !!
1270                  !! conditionalities based on ratios
1271                  !! nitrogen (and iron and carbon)
1272                  if (fsin(ji,jj).le.xsin0) then
1273                     fprd(ji,jj)  = 0.0
1274                     fsld2(ji,jj) = 0.0
1275                  elseif (fsin(ji,jj).lt.fsin1) then
1276                     fprd(ji,jj)  = xuif * ((fsin(ji,jj) - xsin0) / (fsin(ji,jj) + tiny(fsin(ji,jj)))) * (fjld(ji,jj) * fpdlim(ji,jj))
1277                     fsld2(ji,jj) = xuif * ((fsin(ji,jj) - xsin0) / (fsin(ji,jj) + tiny(fsin(ji,jj))))
1278                  elseif (fsin(ji,jj).ge.fsin1) then
1279                     fprd(ji,jj)  = (fjld(ji,jj) * fpdlim(ji,jj))
1280                     fsld2(ji,jj) = 1.0
1281                  endif
1282                  !!
1283                  !! silicon
1284                  if (fsin(ji,jj).lt.fnsi1) then
1285                     fprds(ji,jj) = (fjld(ji,jj) * fsld(ji,jj))
1286                  elseif (fsin(ji,jj).lt.fnsi2) then
1287                     fprds(ji,jj) = xuif * ((fnsi(ji,jj) - xnsi0) / (fnsi(ji,jj) + tiny(fnsi(ji,jj)))) * (fjld(ji,jj) * fsld(ji,jj))
1288                  else
1289                     fprds(ji,jj) = 0.0
1290                  endif     
1291               else
1292                  fsin(ji,jj)  = 0.0
1293                  fnsi(ji,jj)  = 0.0
1294                  fprd(ji,jj)  = 0.0
1295                  fsld2(ji,jj) = 0.0
1296                  fprds(ji,jj) = 0.0
1297               endif
1298
1299# if defined key_debug_medusa
1300               !! report phytoplankton growth (including diatom silicon submodel)
1301               if (idf.eq.1.AND.idfval.eq.1) then
1302                  IF (lwp) write (numout,*) '------------------------------'
1303                  IF (lwp) write (numout,*) 'fsin(',jk,')   = ', fsin(ji,jj)
1304                  IF (lwp) write (numout,*) 'fnsi(',jk,')   = ', fnsi(ji,jj)
1305                  IF (lwp) write (numout,*) 'fsld2(',jk,')  = ', fsld2(ji,jj)
1306                  IF (lwp) write (numout,*) 'fprn(',jk,')   = ', fprn(ji,jj)
1307                  IF (lwp) write (numout,*) 'fprd(',jk,')   = ', fprd(ji,jj)
1308                  IF (lwp) write (numout,*) 'fprds(',jk,')  = ', fprds(ji,jj)
1309               endif
1310# endif
1311
1312               !!----------------------------------------------------------------------
1313               !! Mixed layer primary production
1314               !! this block calculates the amount of primary production that occurs
1315               !! within the upper mixed layer; this allows the separate diagnosis
1316               !! of "sub-surface" primary production; it does assume that short-
1317               !! term variability in mixed layer depth doesn't mess with things
1318               !! though
1319               !!----------------------------------------------------------------------
1320               !!
1321               if (fdep1(ji,jj).le.hmld(ji,jj)) then
1322                  !! this level is entirely in the mixed layer
1323                  fq0 = 1.0
1324               elseif (fsdepw(ji,jj,jk).ge.hmld(ji,jj)) then
1325                  !! this level is entirely below the mixed layer
1326                  fq0 = 0.0
1327               else
1328                  !! this level straddles the mixed layer
1329                  fq0 = (hmld(ji,jj) - fsdepw(ji,jj,jk)) / fse3t(ji,jj,jk)
1330               endif
1331               !!
1332               fprn_ml(ji,jj) = fprn_ml(ji,jj) + (fprn(ji,jj) * zphn(ji,jj) * fse3t(ji,jj,jk) * fq0)
1333               fprd_ml(ji,jj) = fprd_ml(ji,jj) + (fprd(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk) * fq0)
1334               
1335               !!----------------------------------------------------------------------
1336               !! Vertical Integral --
1337               !!----------------------------------------------------------------------
1338               ftot_pn(ji,jj)  = ftot_pn(ji,jj)  + (zphn(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral non-diatom phytoplankton
1339               ftot_pd(ji,jj)  = ftot_pd(ji,jj)  + (zphd(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral diatom phytoplankton
1340               ftot_zmi(ji,jj) = ftot_zmi(ji,jj) + (zzmi(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral microzooplankton
1341               ftot_zme(ji,jj) = ftot_zme(ji,jj) + (zzme(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral mesozooplankton
1342               ftot_det(ji,jj) = ftot_det(ji,jj) + (zdet(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral slow detritus, nitrogen
1343               ftot_dtc(ji,jj) = ftot_dtc(ji,jj) + (zdtc(ji,jj) * fse3t(ji,jj,jk))   !! vertical integral slow detritus, carbon
1344               
1345               !!----------------------------------------------------------------------
1346               !! More chlorophyll calculations
1347               !!----------------------------------------------------------------------
1348               !!
1349               !! frn(ji,jj) = (xthetam / fthetan(ji,jj)) * (fprn(ji,jj) / (fthetan(ji,jj) * xpar(ji,jj,jk)))
1350               !! frd(ji,jj) = (xthetam / fthetad(ji,jj)) * (fprd(ji,jj) / (fthetad(ji,jj) * xpar(ji,jj,jk)))
1351               frn(ji,jj) = (xthetam * fchn(ji,jj) * fnln(ji,jj) * ffln(ji,jj)       ) / (fthetan(ji,jj) + tiny(fthetan(ji,jj)))
1352               !! AXY (12/05/09): there's potentially a problem here; fsld, silicic acid
1353               !!   limitation, is used in the following line to regulate chlorophyll
1354               !!   growth in a manner that is inconsistent with its use in the regulation
1355               !!   of biomass growth; the Mongin term term used in growth is more complex
1356               !!   than the simple multiplicative function used below
1357               !! frd(ji,jj) = (xthetam * fchd(ji,jj) * fnld(ji,jj) * ffld(ji,jj) * fsld(ji,jj)) / (fthetad(ji,jj) + tiny(fthetad(ji,jj)))
1358               !! AXY (12/05/09): this replacement line uses the new variable, fsld2, to
1359               !!   regulate chlorophyll growth
1360               frd(ji,jj) = (xthetamd * fchd(ji,jj) * fnld(ji,jj) * ffld(ji,jj) * fsld2(ji,jj)) / (fthetad(ji,jj) + tiny(fthetad(ji,jj)))
1361
1362# if defined key_debug_medusa
1363               !! report chlorophyll calculations
1364               if (idf.eq.1.AND.idfval.eq.1) then
1365                  IF (lwp) write (numout,*) '------------------------------'
1366                  IF (lwp) write (numout,*) 'fthetan(',jk,') = ', fthetan(ji,jj)
1367                  IF (lwp) write (numout,*) 'fthetad(',jk,') = ', fthetad(ji,jj)
1368                  IF (lwp) write (numout,*) 'frn(',jk,')     = ', frn(ji,jj)
1369                  IF (lwp) write (numout,*) 'frd(',jk,')     = ', frd(ji,jj)
1370               endif
1371# endif
1372
1373               !!----------------------------------------------------------------------
1374               !! Zooplankton Grazing
1375               !! this code supplements the base grazing model with one that
1376               !! considers the C:N ratio of grazed food and balances this against
1377               !! the requirements of zooplankton growth; this model is derived
1378               !! from that of Anderson & Pondaven (2003)
1379               !!
1380               !! the current version of the code assumes a fixed C:N ratio for
1381               !! detritus (in contrast to Anderson & Pondaven, 2003), though the
1382               !! full equations are retained for future extension
1383               !!----------------------------------------------------------------------
1384               !!
1385               !!----------------------------------------------------------------------
1386               !! Microzooplankton first
1387               !!----------------------------------------------------------------------
1388               !!
1389               fmi1(ji,jj)    = (xkmi * xkmi) + (xpmipn * zphn(ji,jj) * zphn(ji,jj)) + (xpmid * zdet(ji,jj) * zdet(ji,jj))
1390               fmi(ji,jj)     = xgmi * zzmi(ji,jj) / fmi1(ji,jj)
1391               fgmipn(ji,jj)  = fmi(ji,jj) * xpmipn * zphn(ji,jj) * zphn(ji,jj)   !! grazing on non-diatoms
1392               fgmid(ji,jj)   = fmi(ji,jj) * xpmid  * zdet(ji,jj) * zdet(ji,jj)   !! grazing on detrital nitrogen
1393# if defined key_roam
1394               fgmidc(ji,jj)  = rsmall !acc
1395               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
1396# else
1397               !! AXY (26/11/08): implicit detrital carbon change
1398               fgmidc(ji,jj)  = xthetad * fgmid(ji,jj)              !! grazing on detrital carbon
1399# endif
1400               !!
1401               !! which translates to these incoming N and C fluxes
1402               finmi(ji,jj)   = (1.0 - xphi) * (fgmipn(ji,jj) + fgmid(ji,jj))
1403               ficmi(ji,jj)   = (1.0 - xphi) * ((xthetapn * fgmipn(ji,jj)) + fgmidc(ji,jj))
1404               !!
1405               !! the ideal food C:N ratio for microzooplankton
1406               !! xbetan = 0.77; xthetaz = 5.625; xbetac = 0.64; xkc = 0.80
1407               fstarmi(ji,jj) = (xbetan * xthetazmi) / (xbetac * xkc)
1408               !!
1409               !! process these to determine proportioning of grazed N and C
1410               !! (since there is no explicit consideration of respiration,
1411               !! only growth and excretion are calculated here)
1412               fmith(ji,jj)   = (ficmi(ji,jj) / (finmi(ji,jj) + tiny(finmi(ji,jj))))
1413               if (fmith(ji,jj).ge.fstarmi(ji,jj)) then
1414                  fmigrow(ji,jj) = xbetan * finmi(ji,jj)
1415                  fmiexcr(ji,jj) = 0.0
1416               else
1417                  fmigrow(ji,jj) = (xbetac * xkc * ficmi(ji,jj)) / xthetazmi
1418                  fmiexcr(ji,jj) = ficmi(ji,jj) * ((xbetan / (fmith(ji,jj) + tiny(fmith(ji,jj)))) - ((xbetac * xkc) / xthetazmi))
1419               endif
1420# if defined key_roam
1421               fmiresp(ji,jj) = (xbetac * ficmi(ji,jj)) - (xthetazmi * fmigrow(ji,jj))
1422# endif
1423
1424# if defined key_debug_medusa
1425               !! report microzooplankton grazing
1426               if (idf.eq.1.AND.idfval.eq.1) then
1427                  IF (lwp) write (numout,*) '------------------------------'
1428                  IF (lwp) write (numout,*) 'fmi1(',jk,')    = ', fmi1(ji,jj)
1429                  IF (lwp) write (numout,*) 'fmi(',jk,')     = ', fmi(ji,jj)
1430                  IF (lwp) write (numout,*) 'fgmipn(',jk,')  = ', fgmipn(ji,jj)
1431                  IF (lwp) write (numout,*) 'fgmid(',jk,')   = ', fgmid(ji,jj)
1432                  IF (lwp) write (numout,*) 'fgmidc(',jk,')  = ', fgmidc(ji,jj)
1433                  IF (lwp) write (numout,*) 'finmi(',jk,')   = ', finmi(ji,jj)
1434                  IF (lwp) write (numout,*) 'ficmi(',jk,')   = ', ficmi(ji,jj)
1435                  IF (lwp) write (numout,*) 'fstarmi(',jk,') = ', fstarmi(ji,jj)
1436                  IF (lwp) write (numout,*) 'fmith(',jk,')   = ', fmith(ji,jj)
1437                  IF (lwp) write (numout,*) 'fmigrow(',jk,') = ', fmigrow(ji,jj)
1438                  IF (lwp) write (numout,*) 'fmiexcr(',jk,') = ', fmiexcr(ji,jj)
1439#  if defined key_roam
1440                  IF (lwp) write (numout,*) 'fmiresp(',jk,') = ', fmiresp(ji,jj)
1441#  endif
1442               endif
1443# endif
1444
1445               !!----------------------------------------------------------------------
1446               !! Mesozooplankton second
1447               !!----------------------------------------------------------------------
1448               !!
1449               fme1(ji,jj)    = (xkme * xkme) + (xpmepn * zphn(ji,jj) * zphn(ji,jj)) + (xpmepd * zphd(ji,jj) * zphd(ji,jj)) + & 
1450                         (xpmezmi * zzmi(ji,jj) * zzmi(ji,jj)) + (xpmed * zdet(ji,jj) * zdet(ji,jj))
1451               fme(ji,jj)     = xgme * zzme(ji,jj) / fme1(ji,jj)
1452               fgmepn(ji,jj)  = fme(ji,jj) * xpmepn  * zphn(ji,jj) * zphn(ji,jj)  !! grazing on non-diatoms
1453               fgmepd(ji,jj)  = fme(ji,jj) * xpmepd  * zphd(ji,jj) * zphd(ji,jj)  !! grazing on diatoms
1454               fgmepds(ji,jj) = fsin(ji,jj) * fgmepd(ji,jj)                !! grazing on diatom silicon
1455               fgmezmi(ji,jj) = fme(ji,jj) * xpmezmi * zzmi(ji,jj) * zzmi(ji,jj)  !! grazing on microzooplankton
1456               fgmed(ji,jj)   = fme(ji,jj) * xpmed   * zdet(ji,jj) * zdet(ji,jj)  !! grazing on detrital nitrogen
1457# if defined key_roam
1458               fgmedc(ji,jj)  = rsmall !acc
1459               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
1460# else
1461               !! AXY (26/11/08): implicit detrital carbon change
1462               fgmedc(ji,jj)  = xthetad * fgmed(ji,jj)              !! grazing on detrital carbon
1463# endif
1464               !!
1465               !! which translates to these incoming N and C fluxes
1466               finme(ji,jj)   = (1.0 - xphi) * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj))
1467               ficme(ji,jj)   = (1.0 - xphi) * ((xthetapn * fgmepn(ji,jj)) + (xthetapd * fgmepd(ji,jj)) + &
1468                        (xthetazmi * fgmezmi(ji,jj)) + fgmedc(ji,jj))
1469               !!
1470               !! the ideal food C:N ratio for mesozooplankton
1471               !! xbetan = 0.77; xthetaz = 5.625; xbetac = 0.64; xkc = 0.80
1472               fstarme(ji,jj) = (xbetan * xthetazme) / (xbetac * xkc)
1473               !!
1474               !! process these to determine proportioning of grazed N and C
1475               !! (since there is no explicit consideration of respiration,
1476               !! only growth and excretion are calculated here)
1477               fmeth(ji,jj)   = (ficme(ji,jj) / (finme(ji,jj) + tiny(finme(ji,jj))))
1478               if (fmeth(ji,jj).ge.fstarme(ji,jj)) then
1479                  fmegrow(ji,jj) = xbetan * finme(ji,jj)
1480                  fmeexcr(ji,jj) = 0.0
1481               else
1482                  fmegrow(ji,jj) = (xbetac * xkc * ficme(ji,jj)) / xthetazme
1483                  fmeexcr(ji,jj) = ficme(ji,jj) * ((xbetan / (fmeth(ji,jj) + tiny(fmeth(ji,jj)))) - ((xbetac * xkc) / xthetazme))
1484               endif
1485# if defined key_roam
1486               fmeresp(ji,jj) = (xbetac * ficme(ji,jj)) - (xthetazme * fmegrow(ji,jj))
1487# endif
1488
1489# if defined key_debug_medusa
1490               !! report mesozooplankton grazing
1491               if (idf.eq.1.AND.idfval.eq.1) then
1492                  IF (lwp) write (numout,*) '------------------------------'
1493                  IF (lwp) write (numout,*) 'fme1(',jk,')    = ', fme1(ji,jj)
1494                  IF (lwp) write (numout,*) 'fme(',jk,')     = ', fme(ji,jj)
1495                  IF (lwp) write (numout,*) 'fgmepn(',jk,')  = ', fgmepn(ji,jj)
1496                  IF (lwp) write (numout,*) 'fgmepd(',jk,')  = ', fgmepd(ji,jj)
1497                  IF (lwp) write (numout,*) 'fgmepds(',jk,') = ', fgmepds(ji,jj)
1498                  IF (lwp) write (numout,*) 'fgmezmi(',jk,') = ', fgmezmi(ji,jj)
1499                  IF (lwp) write (numout,*) 'fgmed(',jk,')   = ', fgmed(ji,jj)
1500                  IF (lwp) write (numout,*) 'fgmedc(',jk,')  = ', fgmedc(ji,jj)
1501                  IF (lwp) write (numout,*) 'finme(',jk,')   = ', finme(ji,jj)
1502                  IF (lwp) write (numout,*) 'ficme(',jk,')   = ', ficme(ji,jj)
1503                  IF (lwp) write (numout,*) 'fstarme(',jk,') = ', fstarme(ji,jj)
1504                  IF (lwp) write (numout,*) 'fmeth(',jk,')   = ', fmeth(ji,jj)
1505                  IF (lwp) write (numout,*) 'fmegrow(',jk,') = ', fmegrow(ji,jj)
1506                  IF (lwp) write (numout,*) 'fmeexcr(',jk,') = ', fmeexcr(ji,jj)
1507#  if defined key_roam
1508                  IF (lwp) write (numout,*) 'fmeresp(',jk,') = ', fmeresp(ji,jj)
1509#  endif
1510               endif
1511# endif
1512
1513               fzmi_i(ji,jj)  = fzmi_i(ji,jj)  + fse3t(ji,jj,jk) * (  &
1514                  fgmipn(ji,jj) + fgmid(ji,jj) )
1515               fzmi_o(ji,jj)  = fzmi_o(ji,jj)  + fse3t(ji,jj,jk) * (  &
1516                  fmigrow(ji,jj) + (xphi * (fgmipn(ji,jj) + fgmid(ji,jj))) + fmiexcr(ji,jj) + ((1.0 - xbetan) * finmi(ji,jj)) )
1517               fzme_i(ji,jj)  = fzme_i(ji,jj)  + fse3t(ji,jj,jk) * (  &
1518                  fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj) )
1519               fzme_o(ji,jj)  = fzme_o(ji,jj)  + fse3t(ji,jj,jk) * (  &
1520                  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)) )
1521
1522               !!----------------------------------------------------------------------
1523               !! Plankton metabolic losses
1524               !! Linear loss processes assumed to be metabolic in origin
1525               !!----------------------------------------------------------------------
1526               !!
1527               fdpn2(ji,jj)  = xmetapn  * zphn(ji,jj)
1528               fdpd2(ji,jj)  = xmetapd  * zphd(ji,jj)
1529               fdpds2(ji,jj) = xmetapd  * zpds(ji,jj)
1530               fdzmi2(ji,jj) = xmetazmi * zzmi(ji,jj)
1531               fdzme2(ji,jj) = xmetazme * zzme(ji,jj)
1532
1533               !!----------------------------------------------------------------------
1534               !! Plankton mortality losses
1535               !! EKP (26/02/09): phytoplankton hyperbolic mortality term introduced
1536               !! to improve performance in gyres
1537               !!----------------------------------------------------------------------
1538               !!
1539               !! non-diatom phytoplankton
1540               if (jmpn.eq.1) fdpn(ji,jj) = xmpn * zphn(ji,jj)               !! linear
1541               if (jmpn.eq.2) fdpn(ji,jj) = xmpn * zphn(ji,jj) * zphn(ji,jj)        !! quadratic
1542               if (jmpn.eq.3) fdpn(ji,jj) = xmpn * zphn(ji,jj) * &           !! hyperbolic
1543                  (zphn(ji,jj) / (xkphn + zphn(ji,jj)))
1544               if (jmpn.eq.4) fdpn(ji,jj) = xmpn * zphn(ji,jj) * &           !! sigmoid
1545                  ((zphn(ji,jj) * zphn(ji,jj)) / (xkphn + (zphn(ji,jj) * zphn(ji,jj))))
1546               !!
1547               !! diatom phytoplankton
1548               if (jmpd.eq.1) fdpd(ji,jj) = xmpd * zphd(ji,jj)               !! linear
1549               if (jmpd.eq.2) fdpd(ji,jj) = xmpd * zphd(ji,jj) * zphd(ji,jj)        !! quadratic
1550               if (jmpd.eq.3) fdpd(ji,jj) = xmpd * zphd(ji,jj) * &           !! hyperbolic
1551                  (zphd(ji,jj) / (xkphd + zphd(ji,jj)))
1552               if (jmpd.eq.4) fdpd(ji,jj) = xmpd * zphd(ji,jj) * &           !! sigmoid
1553                  ((zphd(ji,jj) * zphd(ji,jj)) / (xkphd + (zphd(ji,jj) * zphd(ji,jj))))
1554               fdpds(ji,jj) = fdpd(ji,jj) * fsin(ji,jj)
1555               !!
1556               !! microzooplankton
1557               if (jmzmi.eq.1) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj)            !! linear
1558               if (jmzmi.eq.2) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj) * zzmi(ji,jj)     !! quadratic
1559               if (jmzmi.eq.3) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj) * &        !! hyperbolic
1560                  (zzmi(ji,jj) / (xkzmi + zzmi(ji,jj)))
1561               if (jmzmi.eq.4) fdzmi(ji,jj) = xmzmi * zzmi(ji,jj) * &        !! sigmoid
1562                  ((zzmi(ji,jj) * zzmi(ji,jj)) / (xkzmi + (zzmi(ji,jj) * zzmi(ji,jj))))
1563               !!
1564               !! mesozooplankton
1565               if (jmzme.eq.1) fdzme(ji,jj) = xmzme * zzme(ji,jj)            !! linear
1566               if (jmzme.eq.2) fdzme(ji,jj) = xmzme * zzme(ji,jj) * zzme(ji,jj)     !! quadratic
1567               if (jmzme.eq.3) fdzme(ji,jj) = xmzme * zzme(ji,jj) * &        !! hyperbolic
1568                  (zzme(ji,jj) / (xkzme + zzme(ji,jj)))
1569               if (jmzme.eq.4) fdzme(ji,jj) = xmzme * zzme(ji,jj) * &        !! sigmoid
1570                  ((zzme(ji,jj) * zzme(ji,jj)) / (xkzme + (zzme(ji,jj) * zzme(ji,jj))))
1571
1572               !!----------------------------------------------------------------------
1573               !! Detritus remineralisation
1574               !! Constant or temperature-dependent
1575               !!----------------------------------------------------------------------
1576               !!
1577               if (jmd.eq.1) then
1578                  !! temperature-dependent
1579                  fdd(ji,jj)  = xmd  * fun_T(ji,jj) * zdet(ji,jj)
1580# if defined key_roam
1581                  fddc(ji,jj) = xmdc * fun_T(ji,jj) * zdtc(ji,jj)
1582# endif
1583               elseif (jmd.eq.2) then
1584                  !! AXY (16/05/13): add in Q10-based parameterisation (def in nmlst)
1585                  !! temperature-dependent
1586                  fdd(ji,jj)  = xmd  * fun_Q10(ji,jj) * zdet(ji,jj)
1587#if defined key_roam
1588                  fddc(ji,jj) = xmdc * fun_Q10(ji,jj) * zdtc(ji,jj)
1589#endif
1590               else
1591                  !! temperature-independent
1592                  fdd(ji,jj)  = xmd  * zdet(ji,jj)
1593# if defined key_roam
1594                  fddc(ji,jj) = xmdc * zdtc(ji,jj)
1595# endif
1596               endif
1597               !!
1598               !! AXY (22/07/09): accelerate detrital remineralisation in the bottom box
1599               if ((jk.eq.mbathy(ji,jj)) .and. jsfd.eq.1) then
1600                  fdd(ji,jj)  = 1.0  * zdet(ji,jj)
1601# if defined key_roam
1602                  fddc(ji,jj) = 1.0  * zdtc(ji,jj)
1603# endif
1604               endif
1605               
1606# if defined key_debug_medusa
1607               !! report plankton mortality and remineralisation
1608               if (idf.eq.1.AND.idfval.eq.1) then
1609                  IF (lwp) write (numout,*) '------------------------------'
1610                  IF (lwp) write (numout,*) 'fdpn2(',jk,') = ', fdpn2(ji,jj)
1611                  IF (lwp) write (numout,*) 'fdpd2(',jk,') = ', fdpd2(ji,jj)
1612                  IF (lwp) write (numout,*) 'fdpds2(',jk,')= ', fdpds2(ji,jj)
1613                  IF (lwp) write (numout,*) 'fdzmi2(',jk,')= ', fdzmi2(ji,jj)
1614                  IF (lwp) write (numout,*) 'fdzme2(',jk,')= ', fdzme2(ji,jj)
1615                  IF (lwp) write (numout,*) 'fdpn(',jk,')  = ', fdpn(ji,jj)
1616                  IF (lwp) write (numout,*) 'fdpd(',jk,')  = ', fdpd(ji,jj)
1617                  IF (lwp) write (numout,*) 'fdpds(',jk,') = ', fdpds(ji,jj)
1618                  IF (lwp) write (numout,*) 'fdzmi(',jk,') = ', fdzmi(ji,jj)
1619                  IF (lwp) write (numout,*) 'fdzme(',jk,') = ', fdzme(ji,jj)
1620                  IF (lwp) write (numout,*) 'fdd(',jk,')   = ', fdd(ji,jj)
1621#  if defined key_roam
1622                  IF (lwp) write (numout,*) 'fddc(',jk,')  = ', fddc(ji,jj)
1623#  endif
1624               endif
1625# endif
1626
1627               !!----------------------------------------------------------------------
1628               !! Detritus addition to benthos
1629               !! If activated, slow detritus in the bottom box will enter the
1630               !! benthic pool
1631               !!----------------------------------------------------------------------
1632               !!
1633               if ((jk.eq.mbathy(ji,jj)) .and. jorgben.eq.1) then
1634                  !! this is the BOTTOM OCEAN BOX -> into the benthic pool!
1635                  !!
1636                  f_sbenin_n(ji,jj)  = (zdet(ji,jj) * vsed * 86400.)
1637                  f_sbenin_fe(ji,jj) = (zdet(ji,jj) * vsed * 86400. * xrfn)
1638# if defined key_roam
1639                  f_sbenin_c(ji,jj)  = (zdtc(ji,jj) * vsed * 86400.)
1640# else
1641                  f_sbenin_c(ji,jj)  = (zdet(ji,jj) * vsed * 86400. * xthetad)
1642# endif
1643               endif
1644
1645               !!----------------------------------------------------------------------
1646               !! Iron chemistry and fractionation
1647               !! following the Parekh et al. (2004) scheme adopted by the Met.
1648               !! Office, Medusa models total iron but considers "free" and
1649               !! ligand-bound forms for the purposes of scavenging (only "free"
1650               !! iron can be scavenged
1651               !!----------------------------------------------------------------------
1652               !!
1653               !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
1654               xFeT        = zfer(ji,jj) * 1.e3
1655               !!
1656               !! calculate fractionation (based on Diat-HadOCC; in turn based on Parekh et al., 2004)
1657               xb_coef_tmp = xk_FeL * (xLgT - xFeT) - 1.0
1658               xb2M4ac     = max(((xb_coef_tmp * xb_coef_tmp) + (4.0 * xk_FeL * xLgT)), 0.0)
1659               !!
1660               !! "free" ligand concentration
1661               xLgF        = 0.5 * (xb_coef_tmp + (xb2M4ac**0.5)) / xk_FeL
1662               !!
1663               !! ligand-bound iron concentration
1664               xFeL        = xLgT - xLgF
1665               !!
1666               !! "free" iron concentration (and convert to mmol Fe / m3)
1667               xFeF        = (xFeT - xFeL) * 1.e-3
1668               xFree(ji,jj)= xFeF / (zfer(ji,jj) + tiny(zfer(ji,jj)))
1669               !!
1670               !! scavenging of iron (multiple schemes); I'm only really happy with the
1671               !! first one at the moment - the others involve assumptions (sometimes
1672               !! guessed at by me) that are potentially questionable
1673               !!
1674               if (jiron.eq.1) then
1675                  !!----------------------------------------------------------------------
1676                  !! Scheme 1: Dutkiewicz et al. (2005)
1677                  !! This scheme includes a single scavenging term based solely on a
1678                  !! fixed rate and the availablility of "free" iron
1679                  !!----------------------------------------------------------------------
1680                  !!
1681                  ffescav(ji,jj)     = xk_sc_Fe * xFeF                     ! = mmol/m3/d
1682                  !!
1683                  !!----------------------------------------------------------------------
1684                  !!
1685                  !! Mick's code contains a further (optional) implicit "scavenging" of
1686                  !! iron that sets an upper bound on "free" iron concentration, and
1687                  !! essentially caps the concentration of total iron as xFeL + "free"
1688                  !! iron; since the former is constrained by a fixed total ligand
1689                  !! concentration (= 1.0 umol/m3), and the latter isn't allowed above
1690                  !! this upper bound, total iron is constrained to a maximum of ...
1691                  !!
1692                  !!    xFeL + min(xFeF, 0.3 umol/m3) = 1.0 + 0.3 = 1.3 umol / m3
1693                  !!
1694                  !! In Mick's code, the actual value of total iron is reset to this
1695                  !! sum (i.e. TFe = FeL + Fe'; but Fe' <= 0.3 umol/m3); this isn't
1696                  !! our favoured approach to tracer updating here (not least because
1697                  !! of the leapfrog), so here the amount scavenged is augmented by an
1698                  !! additional amount that serves to drag total iron back towards that
1699                  !! expected from this limitation on iron concentration ...
1700                  !!
1701                  xmaxFeF     = min((xFeF * 1.e3), 0.3)             ! = umol/m3
1702                  !!
1703                  !! Here, the difference between current total Fe and (FeL + Fe') is
1704                  !! calculated and added to the scavenging flux already calculated
1705                  !! above ...
1706                  !!
1707                  fdeltaFe    = (xFeT - (xFeL + xmaxFeF)) * 1.e-3   ! = mmol/m3
1708                  !!
1709                  !! This assumes that the "excess" iron is dissipated with a time-
1710                  !! scale of 1 day; seems reasonable to me ... (famous last words)
1711                  !!
1712                  ffescav(ji,jj)     = ffescav(ji,jj) + fdeltaFe                  ! = mmol/m3/d
1713                  !!
1714# if defined key_deep_fe_fix
1715                  !! AXY (17/01/13)
1716                  !! stop scavenging for iron concentrations below 0.5 umol / m3
1717                  !! at depths greater than 1000 m; this aims to end MEDUSA's
1718                  !! continual loss of iron at depth without impacting things
1719                  !! at the surface too much; the justification for this is that
1720                  !! it appears to be what Mick Follows et al. do in their work
1721                  !! (as evidenced by the iron initial condition they supplied
1722                  !! me with); to be honest, it looks like Follow et al. do this
1723                  !! at shallower depths than 1000 m, but I'll stick with this
1724                  !! for now; I suspect that this seemingly arbitrary approach
1725                  !! effectively "parameterises" the particle-based scavenging
1726                  !! rates that other models use (i.e. at depth there are no
1727                  !! sinking particles, so scavenging stops); it might be fun
1728                  !! justifying this in a paper though!
1729                  !!
1730                  if ((fsdepw(ji,jj,jk).gt.1000.) .and. (xFeT.lt.0.5)) then
1731                     ffescav(ji,jj) = 0.
1732                  endif
1733# endif
1734                  !!
1735               elseif (jiron.eq.2) then
1736                  !!----------------------------------------------------------------------
1737                  !! Scheme 2: Moore et al. (2004)
1738                  !! This scheme includes a single scavenging term that accounts for
1739                  !! both suspended and sinking particles in the water column; this
1740                  !! term scavenges total iron rather than "free" iron
1741                  !!----------------------------------------------------------------------
1742                  !!
1743                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
1744                  xFeT        = zfer(ji,jj) * 1.e3
1745                  !!
1746                  !! this has a base scavenging rate (12% / y) which is modified by local
1747                  !! particle concentration and sinking flux (and dust - but I'm ignoring
1748                  !! that here for now) and which is accelerated when Fe concentration gets
1749                  !! 0.6 nM (= 0.6 umol/m3 = 0.0006 mmol/m3), and decreased as concentrations
1750                  !! below 0.4 nM (= 0.4 umol/m3 = 0.0004 mmol/m3)
1751                  !!
1752                  !! base scavenging rate (0.12 / y)
1753                  fbase_scav = 0.12 / 365.25
1754                  !!
1755                  !! calculate sinking particle part of scaling factor
1756                  !! this takes local fast sinking carbon (mmol C / m2 / d) and
1757                  !! gets it into nmol C / cm3 / s ("rdt" below is the number of seconds in
1758                  !! a model timestep)
1759                  !!
1760                  !! fscal_sink = ffastc(ji,jj) * 1.e2 / (86400.)
1761                  !!
1762                  !! ... actually, re-reading Moore et al.'s equations, it looks like he uses
1763                  !! his sinking flux directly, without scaling it by time-step or anything,
1764                  !! so I'll copy this here ...
1765                  !!
1766                  fscal_sink = ffastc(ji,jj) * 1.e2
1767                  !!
1768                  !! calculate particle part of scaling factor
1769                  !! this totals up the carbon in suspended particles (Pn, Pd, Zmi, Zme, D),
1770                  !! which comes out in mmol C / m3 (= nmol C / cm3), and then multiplies it
1771                  !! by a magic factor, 0.002, to get it into nmol C / cm2 / s
1772                  !!
1773                  fscal_part = ((xthetapn * zphn(ji,jj)) + (xthetapd * zphd(ji,jj)) + (xthetazmi * zzmi(ji,jj)) + &
1774                  (xthetazme * zzme(ji,jj)) + (xthetad * zdet(ji,jj))) * 0.002
1775                  !!
1776                  !! calculate scaling factor for base scavenging rate
1777                  !! this uses the (now correctly scaled) sinking flux and standing
1778                  !! particle concentration, divides through by some sort of reference
1779                  !! value (= 0.0066 nmol C / cm2 / s) and then uses this, or not if its
1780                  !! too high, to rescale the base scavenging rate
1781                  !!
1782                  fscal_scav = fbase_scav * min(((fscal_sink + fscal_part) / 0.0066), 4.0)
1783                  !!
1784                  !! the resulting scavenging rate is then scaled further according to the
1785                  !! local iron concentration (i.e. diminished in low iron regions; enhanced
1786                  !! in high iron regions; less alone in intermediate iron regions)
1787                  !!
1788                  if (xFeT.lt.0.4) then
1789                     !!
1790                     !! low iron region
1791                     !!
1792                     fscal_scav = fscal_scav * (xFeT / 0.4)
1793                     !!
1794                  elseif (xFeT.gt.0.6) then
1795                     !!
1796                     !! high iron region
1797                     !!
1798                     fscal_scav = fscal_scav + ((xFeT / 0.6) * (6.0 / 1.4))
1799                     !!
1800                  else
1801                     !!
1802                     !! intermediate iron region: do nothing
1803                     !!
1804                  endif
1805                  !!
1806                  !! apply the calculated scavenging rate ...
1807                  !!
1808                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj)
1809                  !!
1810               elseif (jiron.eq.3) then
1811                  !!----------------------------------------------------------------------
1812                  !! Scheme 3: Moore et al. (2008)
1813                  !! This scheme includes a single scavenging term that accounts for
1814                  !! sinking particles in the water column, and includes organic C,
1815                  !! biogenic opal, calcium carbonate and dust in this (though the
1816                  !! latter is ignored here until I work out what units the incoming
1817                  !! "dust" flux is in); this term scavenges total iron rather than
1818                  !! "free" iron
1819                  !!----------------------------------------------------------------------
1820                  !!
1821                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
1822                  xFeT        = zfer(ji,jj) * 1.e3
1823                  !!
1824                  !! this has a base scavenging rate which is modified by local
1825                  !! particle sinking flux (including dust - but I'm ignoring that
1826                  !! here for now) and which is accelerated when Fe concentration
1827                  !! is > 0.6 nM (= 0.6 umol/m3 = 0.0006 mmol/m3), and decreased as
1828                  !! concentrations < 0.5 nM (= 0.5 umol/m3 = 0.0005 mmol/m3)
1829                  !!
1830                  !! base scavenging rate (Fe_b in paper; units may be wrong there)
1831                  fbase_scav = 0.00384 ! (ng)^-1 cm
1832                  !!
1833                  !! calculate sinking particle part of scaling factor; this converts
1834                  !! mmol / m2 / d fluxes of organic carbon, silicon and calcium
1835                  !! carbonate into ng / cm2 / s fluxes; it is assumed here that the
1836                  !! mass conversions simply consider the mass of the main element
1837                  !! (C, Si and Ca) and *not* the mass of the molecules that they are
1838                  !! part of; Moore et al. (2008) is unclear on the conversion that
1839                  !! should be used
1840                  !!
1841                  !! milli -> nano; mol -> gram; /m2 -> /cm2; /d -> /s
1842                  fscal_csink  = (ffastc(ji,jj)  * 1.e6 * xmassc  * 1.e-4 / 86400.)      ! ng C  / cm2 / s
1843                  fscal_sisink = (ffastsi(ji,jj) * 1.e6 * xmasssi * 1.e-4 / 86400.)      ! ng Si / cm2 / s
1844                  fscal_casink = (ffastca(ji,jj) * 1.e6 * xmassca * 1.e-4 / 86400.)      ! ng Ca / cm2 / s
1845                  !!
1846                  !! sum up these sinking fluxes and convert to ng / cm by dividing
1847                  !! through by a sinking rate of 100 m / d = 1.157 cm / s
1848                  fscal_sink   = ((fscal_csink * 6.) + fscal_sisink + fscal_casink) / &
1849                  (100. * 1.e3 / 86400)                                                  ! ng / cm
1850                  !!
1851                  !! now calculate the scavenging rate based upon the base rate and
1852                  !! this particle flux scaling; according to the published units,
1853                  !! the result actually has *no* units, but as it must be expressed
1854                  !! per unit time for it to make any sense, I'm assuming a missing
1855                  !! "per second"
1856                  fscal_scav = fbase_scav * fscal_sink                                   ! / s
1857                  !!
1858                  !! the resulting scavenging rate is then scaled further according to the
1859                  !! local iron concentration (i.e. diminished in low iron regions; enhanced
1860                  !! in high iron regions; less alone in intermediate iron regions)
1861                  !!
1862                  if (xFeT.lt.0.5) then
1863                     !!
1864                     !! low iron region (0.5 instead of the 0.4 in Moore et al., 2004)
1865                     !!
1866                     fscal_scav = fscal_scav * (xFeT / 0.5)
1867                     !!
1868                  elseif (xFeT.gt.0.6) then
1869                     !!
1870                     !! high iron region (functional form different in Moore et al., 2004)
1871                     !!
1872                     fscal_scav = fscal_scav + ((xFeT - 0.6) * 0.00904)
1873                     !!
1874                  else
1875                     !!
1876                     !! intermediate iron region: do nothing
1877                     !!
1878                  endif
1879                  !!
1880                  !! apply the calculated scavenging rate ...
1881                  !!
1882                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj)
1883                  !!
1884               elseif (jiron.eq.4) then
1885                  !!----------------------------------------------------------------------
1886                  !! Scheme 4: Galbraith et al. (2010)
1887                  !! This scheme includes two scavenging terms, one for organic,
1888                  !! particle-based scavenging, and another for inorganic scavenging;
1889                  !! both terms scavenge "free" iron only
1890                  !!----------------------------------------------------------------------
1891                  !!
1892                  !! Galbraith et al. (2010) present a more straightforward outline of
1893                  !! the scheme in Parekh et al. (2005) ...
1894                  !!
1895                  !! sinking particulate carbon available for scavenging
1896                  !! this assumes a sinking rate of 100 m / d (Moore & Braucher, 2008),
1897                  xCscav1     = (ffastc(ji,jj) * xmassc) / 100. ! = mg C / m3
1898                  !!
1899                  !! scale by Honeyman et al. (1981) exponent coefficient
1900                  !! multiply by 1.e-3 to express C flux in g C rather than mg C
1901                  xCscav2     = (xCscav1 * 1.e-3)**0.58
1902                  !!
1903                  !! multiply by Galbraith et al. (2010) scavenging rate
1904                  xk_org      = 0.5 ! ((g C m/3)^-1) / d
1905                  xORGscav    = xk_org * xCscav2 * xFeF
1906                  !!
1907                  !! Galbraith et al. (2010) also include an inorganic bit ...
1908                  !!
1909                  !! this occurs at a fixed rate, again based on the availability of
1910                  !! "free" iron
1911                  !!
1912                  !! k_inorg  = 1000 d**-1 nmol Fe**-0.5 kg**-0.5
1913                  !!
1914                  !! to implement this here, scale xFeF by 1026 to put in units of
1915                  !! umol/m3 which approximately equal nmol/kg
1916                  !!
1917                  xk_inorg    = 1000. ! ((nmol Fe / kg)^1.5)
1918                  xINORGscav  = (xk_inorg * (xFeF * 1026.)**1.5) * 1.e-3
1919                  !!
1920                  !! sum these two terms together
1921                  ffescav(ji,jj)     = xORGscav + xINORGscav
1922               else
1923                  !!----------------------------------------------------------------------
1924                  !! No Scheme: you coward!
1925                  !! This scheme puts its head in the sand and eskews any decision about
1926                  !! how iron is removed from the ocean; prepare to get deluged in iron
1927                  !! you fool!
1928                  !!----------------------------------------------------------------------
1929                  ffescav(ji,jj)     = 0.
1930               endif
1931
1932               !!----------------------------------------------------------------------
1933               !! Other iron cycle processes
1934               !!----------------------------------------------------------------------
1935               !!
1936               !! aeolian iron deposition
1937               if (jk.eq.1) then
1938                  !! zirondep   is in mmol-Fe / m2 / day
1939                  !! ffetop(ji,jj)     is in mmol-dissolved-Fe / m3 / day
1940                  ffetop(ji,jj)  = zirondep(ji,jj) * xfe_sol / fse3t(ji,jj,jk) 
1941               else
1942                  ffetop(ji,jj)  = 0.0
1943               endif
1944               !!
1945               !! seafloor iron addition
1946               !! AXY (10/07/12): amended to only apply sedimentary flux up to ~500 m down
1947               !! if (jk.eq.(mbathy(ji,jj)-1).AND.jk.lt.i1100) then
1948               if ((jk.eq.mbathy(ji,jj)).AND.jk.le.i0500) then
1949                  !! Moore et al. (2004) cite a coastal California value of 5 umol/m2/d, but adopt a
1950                  !! global value of 2 umol/m2/d for all areas < 1100 m; here we use this latter value
1951                  !! but apply it everywhere
1952                  !! AXY (21/07/09): actually, let's just apply it below 1100 m (levels 1-37)
1953                  ffebot(ji,jj)  = (xfe_sed / fse3t(ji,jj,jk))
1954               else
1955                  ffebot(ji,jj)  = 0.0
1956               endif
1957
1958               !! AXY (16/12/09): remove iron addition/removal processes
1959               !! For the purposes of the quarter degree run, the iron cycle is being pegged to the
1960               !! initial condition supplied by Mick Follows via restoration with a 30 day period;
1961               !! iron addition at the seafloor is still permitted with the idea that this extra
1962               !! iron will be removed by the restoration away from the source
1963               !! ffescav(ji,jj) = 0.0
1964               !! ffetop(ji,jj)  = 0.0
1965               !! ffebot(ji,jj)  = 0.0
1966
1967# if defined key_debug_medusa
1968               !! report miscellaneous calculations
1969               if (idf.eq.1.AND.idfval.eq.1) then
1970                  IF (lwp) write (numout,*) '------------------------------'
1971                  IF (lwp) write (numout,*) 'xfe_sol  = ', xfe_sol
1972                  IF (lwp) write (numout,*) 'xfe_mass = ', xfe_mass
1973                  IF (lwp) write (numout,*) 'ffetop(',jk,')  = ', ffetop(ji,jj)
1974                  IF (lwp) write (numout,*) 'ffebot(',jk,')  = ', ffebot(ji,jj)
1975                  IF (lwp) write (numout,*) 'xFree(',jk,')   = ', xFree(ji,jj)
1976                  IF (lwp) write (numout,*) 'ffescav(',jk,') = ', ffescav(ji,jj)
1977               endif
1978# endif
1979
1980               !!----------------------------------------------------------------------
1981               !! Miscellaneous
1982               !!----------------------------------------------------------------------
1983               !!
1984               !! diatom frustule dissolution
1985               fsdiss(ji,jj)  = xsdiss * zpds(ji,jj)
1986
1987# if defined key_debug_medusa
1988               !! report miscellaneous calculations
1989               if (idf.eq.1.AND.idfval.eq.1) then
1990                  IF (lwp) write (numout,*) '------------------------------'
1991                  IF (lwp) write (numout,*) 'fsdiss(',jk,')  = ', fsdiss(ji,jj)
1992               endif
1993# endif
1994
1995               !!----------------------------------------------------------------------
1996               !! Slow detritus creation
1997               !!----------------------------------------------------------------------
1998               !! this variable integrates the creation of slow sinking detritus
1999               !! to allow the split between fast and slow detritus to be
2000               !! diagnosed
2001               fslown(ji,jj)  = fdpn(ji,jj) + fdzmi(ji,jj) + ((1.0 - xfdfrac1) * fdpd(ji,jj)) + &
2002               ((1.0 - xfdfrac2) * fdzme(ji,jj)) + ((1.0 - xbetan) * (finmi(ji,jj) + finme(ji,jj)))
2003               !!
2004               !! this variable records the slow detrital sinking flux at this
2005               !! particular depth; it is used in the output of this flux at
2006               !! standard depths in the diagnostic outputs; needs to be
2007               !! adjusted from per second to per day because of parameter vsed
2008               fslownflux(ji,jj) = zdet(ji,jj) * vsed * 86400.
2009# if defined key_roam
2010               !!
2011               !! and the same for detrital carbon
2012               fslowc(ji,jj)  = (xthetapn * fdpn(ji,jj)) + (xthetazmi * fdzmi(ji,jj)) + &
2013               (xthetapd * (1.0 - xfdfrac1) * fdpd(ji,jj)) + &
2014               (xthetazme * (1.0 - xfdfrac2) * fdzme(ji,jj)) + &
2015               ((1.0 - xbetac) * (ficmi(ji,jj) + ficme(ji,jj)))
2016               !!
2017               !! this variable records the slow detrital sinking flux at this
2018               !! particular depth; it is used in the output of this flux at
2019               !! standard depths in the diagnostic outputs; needs to be
2020               !! adjusted from per second to per day because of parameter vsed
2021               fslowcflux(ji,jj) = zdtc(ji,jj) * vsed * 86400.
2022# endif
2023
2024               !!----------------------------------------------------------------------
2025               !! Nutrient regeneration
2026               !! this variable integrates total nitrogen regeneration down the
2027               !! watercolumn; its value is stored and output as a 2D diagnostic;
2028               !! the corresponding dissolution flux of silicon (from sources
2029               !! other than fast detritus) is also integrated; note that,
2030               !! confusingly, the linear loss terms from plankton compartments
2031               !! are labelled as fdX2 when one might have expected fdX or fdX1
2032               !!----------------------------------------------------------------------
2033               !!
2034               !! nitrogen
2035               fregen(ji,jj)   = (( (xphi * (fgmipn(ji,jj) + fgmid(ji,jj))) +                &  ! messy feeding
2036               (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj))) +           &  ! messy feeding
2037               fmiexcr(ji,jj) + fmeexcr(ji,jj) + fdd(ji,jj) +                                &  ! excretion + D remin.
2038               fdpn2(ji,jj) + fdpd2(ji,jj) + fdzmi2(ji,jj) + fdzme2(ji,jj)) * fse3t(ji,jj,jk))                    ! linear mortality
2039               !!
2040               !! silicon
2041               fregensi(ji,jj) = (( fsdiss(ji,jj) + ((1.0 - xfdfrac1) * fdpds(ji,jj)) +      &  ! dissolution + non-lin. mortality
2042               ((1.0 - xfdfrac3) * fgmepds(ji,jj)) +                           &  ! egestion by zooplankton
2043               fdpds2(ji,jj)) * fse3t(ji,jj,jk))                                             ! linear mortality
2044# if defined key_roam
2045               !!
2046               !! carbon
2047! Doesn't look this is used - marc 10/4/17
2048!               fregenc(ji,jj)  = (( (xphi * ((xthetapn * fgmipn(ji,jj)) + fgmidc(ji,jj))) +  &  ! messy feeding
2049!               (xphi * ((xthetapn * fgmepn(ji,jj)) + (xthetapd * fgmepd(ji,jj)) +     &  ! messy feeding
2050!               (xthetazmi * fgmezmi(ji,jj)) + fgmedc(ji,jj))) +                       &  ! messy feeding
2051!               fmiresp(ji,jj) + fmeresp(ji,jj) + fddc(ji,jj) +                               &  ! respiration + D remin.
2052!               (xthetapn * fdpn2(ji,jj)) + (xthetapd * fdpd2(ji,jj)) +                &  ! linear mortality
2053!               (xthetazmi * fdzmi2(ji,jj)) + (xthetazme * fdzme2(ji,jj))) * fse3t(ji,jj,jk))        ! linear mortality
2054# endif
2055
2056               !!----------------------------------------------------------------------
2057               !! Fast-sinking detritus terms
2058               !! "local" variables declared so that conservation can be checked;
2059               !! the calculated terms are added to the fast-sinking flux later on
2060               !! only after the flux entering this level has experienced some
2061               !! remineralisation
2062               !! note: these fluxes need to be scaled by the level thickness
2063               !!----------------------------------------------------------------------
2064               !!
2065               !! nitrogen:   diatom and mesozooplankton mortality
2066               ftempn(ji,jj)         = b0 * ((xfdfrac1 * fdpd(ji,jj))  + (xfdfrac2 * fdzme(ji,jj)))
2067               !!
2068               !! silicon:    diatom mortality and grazed diatoms
2069               ftempsi(ji,jj)        = b0 * ((xfdfrac1 * fdpds(ji,jj)) + (xfdfrac3 * fgmepds(ji,jj)))
2070               !!
2071               !! iron:       diatom and mesozooplankton mortality
2072               ftempfe(ji,jj)        = b0 * (((xfdfrac1 * fdpd(ji,jj)) + (xfdfrac2 * fdzme(ji,jj))) * xrfn)
2073               !!
2074               !! carbon:     diatom and mesozooplankton mortality
2075               ftempc(ji,jj)         = b0 * ((xfdfrac1 * xthetapd * fdpd(ji,jj)) + & 
2076                                (xfdfrac2 * xthetazme * fdzme(ji,jj)))
2077               !!
2078# if defined key_roam
2079               if (jrratio.eq.0) then
2080                  !! CaCO3:      latitudinally-based fraction of total primary production
2081                  !!               0.10 at equator; 0.02 at pole
2082                  fcaco3(ji,jj)         = xcaco3a + ((xcaco3b - xcaco3a) * ((90.0 - abs(gphit(ji,jj))) / 90.0))
2083               elseif (jrratio.eq.1) then
2084                  !! CaCO3:      Ridgwell et al. (2007) submodel, version 1
2085                  !!             this uses SURFACE omega calcite to regulate rain ratio
2086                  if (f_omcal(ji,jj).ge.1.0) then
2087                     fq1 = (f_omcal(ji,jj) - 1.0)**0.81
2088                  else
2089                     fq1 = 0.
2090                  endif
2091                  fcaco3(ji,jj) = xridg_r0 * fq1
2092               elseif (jrratio.eq.2) then
2093                  !! CaCO3:      Ridgwell et al. (2007) submodel, version 2
2094                  !!             this uses FULL 3D omega calcite to regulate rain ratio
2095                  if (f3_omcal(ji,jj,jk).ge.1.0) then
2096                     fq1 = (f3_omcal(ji,jj,jk) - 1.0)**0.81
2097                  else
2098                     fq1 = 0.
2099                  endif
2100                  fcaco3(ji,jj) = xridg_r0 * fq1
2101               endif
2102# else
2103               !! CaCO3:      latitudinally-based fraction of total primary production
2104               !!               0.10 at equator; 0.02 at pole
2105               fcaco3(ji,jj)         = xcaco3a + ((xcaco3b - xcaco3a) * ((90.0 - abs(gphit(ji,jj))) / 90.0))
2106# endif
2107               !! AXY (09/03/09): convert CaCO3 production from function of
2108               !! primary production into a function of fast-sinking material;
2109               !! technically, this is what Dunne et al. (2007) do anyway; they
2110               !! convert total primary production estimated from surface
2111               !! chlorophyll to an export flux for which they apply conversion
2112               !! factors to estimate the various elemental fractions (Si, Ca)
2113               ftempca(ji,jj)        = ftempc(ji,jj) * fcaco3(ji,jj)
2114
2115# if defined key_debug_medusa
2116               !! integrate total fast detritus production
2117               if (idf.eq.1) then
2118                  fifd_n(ji,jj)  = fifd_n(ji,jj)  + (ftempn(ji,jj)  * fse3t(ji,jj,jk))
2119                  fifd_si(ji,jj) = fifd_si(ji,jj) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))
2120                  fifd_fe(ji,jj) = fifd_fe(ji,jj) + (ftempfe(ji,jj) * fse3t(ji,jj,jk))
2121#  if defined key_roam
2122                  fifd_c(ji,jj)  = fifd_c(ji,jj)  + (ftempc(ji,jj)  * fse3t(ji,jj,jk))
2123#  endif
2124               endif
2125
2126               !! report quantities of fast-sinking detritus for each component
2127               if (idf.eq.1.AND.idfval.eq.1) then
2128                  IF (lwp) write (numout,*) '------------------------------'
2129                  IF (lwp) write (numout,*) 'fdpd(',jk,')    = ', fdpd(ji,jj)
2130                  IF (lwp) write (numout,*) 'fdzme(',jk,')   = ', fdzme(ji,jj)
2131                  IF (lwp) write (numout,*) 'ftempn(',jk,')  = ', ftempn(ji,jj)
2132                  IF (lwp) write (numout,*) 'ftempsi(',jk,') = ', ftempsi(ji,jj)
2133                  IF (lwp) write (numout,*) 'ftempfe(',jk,') = ', ftempfe(ji,jj)
2134                  IF (lwp) write (numout,*) 'ftempc(',jk,')  = ', ftempc(ji,jj)
2135                  IF (lwp) write (numout,*) 'ftempca(',jk,') = ', ftempca(ji,jj)
2136                  IF (lwp) write (numout,*) 'flat(',jk,')    = ', abs(gphit(ji,jj))
2137                  IF (lwp) write (numout,*) 'fcaco3(',jk,')  = ', fcaco3(ji,jj)
2138               endif
2139# endif
2140
2141               !!----------------------------------------------------------------------
2142               !! This version of MEDUSA offers a choice of three methods for
2143               !! handling the remineralisation of fast detritus.  All three
2144               !! do so in broadly the same way:
2145               !!
2146               !!   1.  Fast detritus is stored as a 2D array                   [ ffastX  ]
2147               !!   2.  Fast detritus is added level-by-level                   [ ftempX  ]
2148               !!   3.  Fast detritus is not remineralised in the top box       [ freminX ]
2149               !!   4.  Remaining fast detritus is remineralised in the bottom  [ fsedX   ]
2150               !!       box
2151               !!
2152               !! The three remineralisation methods are:
2153               !!   
2154               !!   1.  Ballast model (i.e. that published in Yool et al., 2011)
2155               !!  (1b. Ballast-sans-ballast model)
2156               !!   2.  Martin et al. (1987)
2157               !!   3.  Henson et al. (2011)
2158               !!
2159               !! The first of these couples C, N and Fe remineralisation to
2160               !! the remineralisation of particulate Si and CaCO3, but the
2161               !! latter two treat remineralisation of C, N, Fe, Si and CaCO3
2162               !! completely separately.  At present a switch within the code
2163               !! regulates which submodel is used, but this should be moved
2164               !! to the namelist file.
2165               !!
2166               !! The ballast-sans-ballast submodel is an original development
2167               !! feature of MEDUSA in which the ballast submodel's general
2168               !! framework and parameterisation is used, but in which there
2169               !! is no protection of organic material afforded by ballasting
2170               !! minerals.  While similar, it is not the same as the Martin
2171               !! et al. (1987) submodel.
2172               !!
2173               !! Since the three submodels behave the same in terms of
2174               !! accumulating sinking material and remineralising it all at
2175               !! the seafloor, these portions of the code below are common to
2176               !! all three.
2177               !!----------------------------------------------------------------------
2178
2179               if (jexport.eq.1) then
2180                  !!======================================================================
2181                  !! BALLAST SUBMODEL
2182                  !!======================================================================
2183                  !!
2184                  !!----------------------------------------------------------------------
2185                  !! Fast-sinking detritus fluxes, pt. 1: REMINERALISATION
2186                  !! aside from explicitly modelled, slow-sinking detritus, the
2187                  !! model includes an implicit representation of detrital
2188                  !! particles that sink too quickly to be modelled with
2189                  !! explicit state variables; this sinking flux is instead
2190                  !! instantaneously remineralised down the water column using
2191                  !! the version of Armstrong et al. (2002)'s ballast model
2192                  !! used by Dunne et al. (2007); the version of this model
2193                  !! here considers silicon and calcium carbonate ballast
2194                  !! minerals; this section of the code redistributes the fast
2195                  !! sinking material generated locally down the water column;
2196                  !! this differs from Dunne et al. (2007) in that fast sinking
2197                  !! material is distributed at *every* level below that it is
2198                  !! generated, rather than at every level below some fixed
2199                  !! depth; this scheme is also different in that sinking material
2200                  !! generated in one level is aggregated with that generated by
2201                  !! shallower levels; this should make the ballast model more
2202                  !! self-consistent (famous last words)
2203                  !!----------------------------------------------------------------------
2204                  !!
2205                  if (jk.eq.1) then
2206                     !! this is the SURFACE OCEAN BOX (no remineralisation)
2207                     !!
2208                     freminc(ji,jj)  = 0.0
2209                     freminn(ji,jj)  = 0.0
2210                     freminfe(ji,jj) = 0.0
2211                     freminsi(ji,jj) = 0.0
2212                     freminca(ji,jj) = 0.0
2213                  elseif (jk.le.mbathy(ji,jj)) then
2214                     !! this is an OCEAN BOX (remineralise some material)
2215                     !!
2216                     !! set up CCD depth to be used depending on user choice
2217                     if (jocalccd.eq.0) then
2218                        !! use default CCD field
2219                        fccd_dep(ji,jj) = ocal_ccd(ji,jj)
2220                     elseif (jocalccd.eq.1) then
2221                        !! use calculated CCD field
2222                        fccd_dep(ji,jj) = f2_ccd_cal(ji,jj)
2223                     endif
2224                     !!
2225                     !! === organic carbon ===
2226                     fq0      = ffastc(ji,jj)                        !! how much organic C enters this box        (mol)
2227                     if (iball.eq.1) then
2228                        fq1      = (fq0 * xmassc)                    !! how much it weighs                        (mass)
2229                        fq2      = (ffastca(ji,jj) * xmassca)        !! how much CaCO3 enters this box            (mass)
2230                        fq3      = (ffastsi(ji,jj) * xmasssi)        !! how much  opal enters this box            (mass)
2231                        fq4      = (fq2 * xprotca) + (fq3 * xprotsi) !! total protected organic C                 (mass)
2232                        !! this next term is calculated for C but used for N and Fe as well
2233                        !! it needs to be protected in case ALL C is protected
2234                        if (fq4.lt.fq1) then
2235                           fprotf(ji,jj)   = (fq4 / (fq1 + tiny(fq1)))      !! protected fraction of total organic C     (non-dim)
2236                        else
2237                           fprotf(ji,jj)   = 1.0                            !! all organic C is protected                (non-dim)
2238                        endif
2239                        fq5      = (1.0 - fprotf(ji,jj))                    !! unprotected fraction of total organic C   (non-dim)
2240                        fq6      = (fq0 * fq5)                       !! how much organic C is unprotected         (mol)
2241                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))     !! how much unprotected C leaves this box    (mol)
2242                        fq8      = (fq7 + (fq0 * fprotf(ji,jj)))            !! how much total C leaves this box          (mol)
2243                        freminc(ji,jj)  = (fq0 - fq8) / fse3t(ji,jj,jk)                !! C remineralisation in this box            (mol)
2244                        ffastc(ji,jj) = fq8                         
2245# if defined key_debug_medusa
2246                        !! report in/out/remin fluxes of carbon for this level
2247                           if (idf.eq.1.AND.idfval.eq.1) then
2248                              IF (lwp) write (numout,*) '------------------------------'
2249                              IF (lwp) write (numout,*) 'totalC(',jk,')  = ', fq1
2250                              IF (lwp) write (numout,*) 'prtctC(',jk,')  = ', fq4
2251                              IF (lwp) write (numout,*) 'fprotf(',jk,')  = ', fprotf(ji,jj)
2252                              IF (lwp) write (numout,*) '------------------------------'
2253                              IF (lwp) write (numout,*) 'IN   C(',jk,')  = ', fq0
2254                              IF (lwp) write (numout,*) 'LOST C(',jk,')  = ', freminc(ji,jj) * fse3t(ji,jj,jk)
2255                              IF (lwp) write (numout,*) 'OUT  C(',jk,')  = ', fq8
2256                              IF (lwp) write (numout,*) 'NEW  C(',jk,')  = ', ftempc(ji,jj) * fse3t(ji,jj,jk)
2257                           endif
2258# endif
2259                        else
2260                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))       !! how much organic C leaves this box        (mol)
2261                        freminc(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                !! C remineralisation in this box            (mol)
2262                        ffastc(ji,jj)  = fq1
2263                     endif
2264                     !!
2265                     !! === organic nitrogen ===
2266                     fq0      = ffastn(ji,jj)                        !! how much organic N enters this box        (mol)
2267                     if (iball.eq.1) then
2268                        fq5      = (1.0 - fprotf(ji,jj))                    !! unprotected fraction of total organic N   (non-dim)
2269                        fq6      = (fq0 * fq5)                       !! how much organic N is unprotected         (mol)
2270                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))     !! how much unprotected N leaves this box    (mol)
2271                        fq8      = (fq7 + (fq0 * fprotf(ji,jj)))            !! how much total N leaves this box          (mol)
2272                        freminn(ji,jj)  = (fq0 - fq8) / fse3t(ji,jj,jk)                !! N remineralisation in this box            (mol)
2273                        ffastn(ji,jj)  = fq8
2274# if defined key_debug_medusa
2275                        !! report in/out/remin fluxes of carbon for this level
2276                        if (idf.eq.1.AND.idfval.eq.1) then
2277                           IF (lwp) write (numout,*) '------------------------------'
2278                           IF (lwp) write (numout,*) 'totalN(',jk,')  = ', fq1
2279                           IF (lwp) write (numout,*) 'prtctN(',jk,')  = ', fq4
2280                           IF (lwp) write (numout,*) 'fprotf(',jk,')  = ', fprotf(ji,jj)
2281                           IF (lwp) write (numout,*) '------------------------------'
2282                           if (freminn(ji,jj) < 0.0) then
2283                              IF (lwp) write (numout,*) '** FREMIN ERROR **'
2284                           endif
2285                           IF (lwp) write (numout,*) 'IN   N(',jk,')  = ', fq0
2286                           IF (lwp) write (numout,*) 'LOST N(',jk,')  = ', freminn(ji,jj) * fse3t(ji,jj,jk)
2287                           IF (lwp) write (numout,*) 'OUT  N(',jk,')  = ', fq8
2288                           IF (lwp) write (numout,*) 'NEW  N(',jk,')  = ', ftempn(ji,jj) * fse3t(ji,jj,jk)
2289                        endif
2290# endif
2291                     else
2292                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))       !! how much organic N leaves this box        (mol)
2293                        freminn(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                !! N remineralisation in this box            (mol)
2294                        ffastn(ji,jj)  = fq1
2295                     endif
2296                     !!
2297                     !! === organic iron ===
2298                     fq0      = ffastfe(ji,jj)                       !! how much organic Fe enters this box       (mol)
2299                     if (iball.eq.1) then
2300                        fq5      = (1.0 - fprotf(ji,jj))                    !! unprotected fraction of total organic Fe  (non-dim)
2301                        fq6      = (fq0 * fq5)                       !! how much organic Fe is unprotected        (mol)
2302                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))     !! how much unprotected Fe leaves this box   (mol)
2303                        fq8      = (fq7 + (fq0 * fprotf(ji,jj)))            !! how much total Fe leaves this box         (mol)           
2304                        freminfe(ji,jj) = (fq0 - fq8) / fse3t(ji,jj,jk)                !! Fe remineralisation in this box           (mol)
2305                        ffastfe(ji,jj) = fq8
2306                     else
2307                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))       !! how much total Fe leaves this box         (mol)     
2308                        freminfe(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Fe remineralisation in this box           (mol)
2309                        ffastfe(ji,jj) = fq1
2310                     endif
2311                     !!
2312                     !! === biogenic silicon ===
2313                     fq0      = ffastsi(ji,jj)                       !! how much  opal centers this box           (mol)
2314                     fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastsi))         !! how much  opal leaves this box            (mol)
2315                     freminsi(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! Si remineralisation in this box           (mol)
2316                     ffastsi(ji,jj) = fq1
2317                     !!
2318                     !! === biogenic calcium carbonate ===
2319                     fq0      = ffastca(ji,jj)                       !! how much CaCO3 enters this box            (mol)
2320                     if (fsdepw(ji,jj,jk).le.fccd_dep(ji,jj)) then
2321                        !! whole grid cell above CCD
2322                        fq1      = fq0                               !! above lysocline, no Ca dissolves          (mol)
2323                        freminca(ji,jj) = 0.0                               !! above lysocline, no Ca dissolves          (mol)
2324                        fccd(ji,jj) = real(jk)                       !! which is the last level above the CCD?    (#)
2325                     elseif (fsdepw(ji,jj,jk).ge.fccd_dep(ji,jj)) then
2326                        !! whole grid cell below CCD
2327                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastca))      !! how much CaCO3 leaves this box            (mol)
2328                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2329                     else
2330                        !! partial grid cell below CCD
2331                        fq2      = fdep1(ji,jj) - fccd_dep(ji,jj)                  !! amount of grid cell below CCD             (m)
2332                        fq1      = fq0 * exp(-(fq2 / xfastca))       !! how much CaCO3 leaves this box            (mol)
2333                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2334                     endif
2335                     ffastca(ji,jj) = fq1 
2336                  else
2337                     !! this is BELOW THE LAST OCEAN BOX (do nothing)
2338                     freminc(ji,jj)  = 0.0
2339                     freminn(ji,jj)  = 0.0
2340                     freminfe(ji,jj) = 0.0
2341                     freminsi(ji,jj) = 0.0
2342                     freminca(ji,jj) = 0.0             
2343                  endif
2344
2345               elseif (jexport.eq.2.or.jexport.eq.3) then
2346                  if (jexport.eq.2) then
2347                     !!======================================================================
2348                     !! MARTIN ET AL. (1987) SUBMODEL
2349                     !!======================================================================
2350                     !!
2351                     !!----------------------------------------------------------------------
2352                     !! This submodel uses the classic Martin et al. (1987) curve
2353                     !! to determine the attenuation of fast-sinking detritus down
2354                     !! the water column.  All three organic elements, C, N and Fe,
2355                     !! are handled identically, and their quantities in sinking
2356                     !! particles attenuate according to a power relationship
2357                     !! governed by parameter "b".  This is assigned a canonical
2358                     !! value of -0.858.  Biogenic opal and calcium carbonate are
2359                     !! attentuated using the same function as in the ballast
2360                     !! submodel
2361                     !!----------------------------------------------------------------------
2362                     !!
2363                     fb_val = -0.858
2364                  elseif (jexport.eq.3) then
2365                     !!======================================================================
2366                     !! HENSON ET AL. (2011) SUBMODEL
2367                     !!======================================================================
2368                     !!
2369                     !!----------------------------------------------------------------------
2370                     !! This submodel reconfigures the Martin et al. (1987) curve by
2371                     !! allowing the "b" value to vary geographically.  Its value is
2372                     !! set, following Henson et al. (2011), as a function of local
2373                     !! sea surface temperature:
2374                     !!   b = -1.06 + (0.024 * SST)
2375                     !! This means that remineralisation length scales are longer in
2376                     !! warm, tropical areas and shorter in cold, polar areas.  This
2377                     !! does seem back-to-front (i.e. one would expect GREATER
2378                     !! remineralisation in warmer waters), but is an outcome of
2379                     !! analysis of sediment trap data, and it may reflect details
2380                     !! of ecosystem structure that pertain to particle production
2381                     !! rather than simply Q10.
2382                     !!----------------------------------------------------------------------
2383                     !!
2384                     fl_sst = tsn(ji,jj,1,jp_tem)
2385                     fb_val = -1.06 + (0.024 * fl_sst)
2386                  endif
2387                  !!   
2388                  if (jk.eq.1) then
2389                     !! this is the SURFACE OCEAN BOX (no remineralisation)
2390                     !!
2391                     freminc(ji,jj)  = 0.0
2392                     freminn(ji,jj)  = 0.0
2393                     freminfe(ji,jj) = 0.0
2394                     freminsi(ji,jj) = 0.0
2395                     freminca(ji,jj) = 0.0
2396                  elseif (jk.le.mbathy(ji,jj)) then
2397                     !! this is an OCEAN BOX (remineralise some material)
2398                     !!
2399                     !! === organic carbon ===
2400                     fq0      = ffastc(ji,jj)                        !! how much organic C enters this box        (mol)
2401                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)         !! how much organic C leaves this box        (mol)
2402                     freminc(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! C remineralisation in this box            (mol)
2403                     ffastc(ji,jj)  = fq1
2404                     !!
2405                     !! === organic nitrogen ===
2406                     fq0      = ffastn(ji,jj)                        !! how much organic N enters this box        (mol)
2407                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)         !! how much organic N leaves this box        (mol)
2408                     freminn(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! N remineralisation in this box            (mol)
2409                     ffastn(ji,jj)  = fq1
2410                     !!
2411                     !! === organic iron ===
2412                     fq0      = ffastfe(ji,jj)                       !! how much organic Fe enters this box       (mol)
2413                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)         !! how much organic Fe leaves this box       (mol)
2414                     freminfe(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! Fe remineralisation in this box           (mol)
2415                     ffastfe(ji,jj) = fq1
2416                     !!
2417                     !! === biogenic silicon ===
2418                     fq0      = ffastsi(ji,jj)                       !! how much  opal centers this box           (mol)
2419                     fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastsi))         !! how much  opal leaves this box            (mol)
2420                     freminsi(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                   !! Si remineralisation in this box           (mol)
2421                     ffastsi(ji,jj) = fq1
2422                     !!
2423                     !! === biogenic calcium carbonate ===
2424                     fq0      = ffastca(ji,jj)                       !! how much CaCO3 enters this box            (mol)
2425                     if (fsdepw(ji,jj,jk).le.ocal_ccd(ji,jj)) then
2426                        !! whole grid cell above CCD
2427                        fq1      = fq0                               !! above lysocline, no Ca dissolves          (mol)
2428                        freminca(ji,jj) = 0.0                               !! above lysocline, no Ca dissolves          (mol)
2429                        fccd(ji,jj) = real(jk)                       !! which is the last level above the CCD?    (#)
2430                     elseif (fsdepw(ji,jj,jk).ge.ocal_ccd(ji,jj)) then
2431                        !! whole grid cell below CCD
2432                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastca))      !! how much CaCO3 leaves this box            (mol)
2433                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2434                     else
2435                        !! partial grid cell below CCD
2436                        fq2      = fdep1(ji,jj) - ocal_ccd(ji,jj)           !! amount of grid cell below CCD             (m)
2437                        fq1      = fq0 * exp(-(fq2 / xfastca))       !! how much CaCO3 leaves this box            (mol)
2438                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)                !! Ca remineralisation in this box           (mol)
2439                     endif
2440                     ffastca(ji,jj) = fq1 
2441                  else
2442                     !! this is BELOW THE LAST OCEAN BOX (do nothing)
2443                     freminc(ji,jj)  = 0.0
2444                     freminn(ji,jj)  = 0.0
2445                     freminfe(ji,jj) = 0.0
2446                     freminsi(ji,jj) = 0.0
2447                     freminca(ji,jj) = 0.0             
2448                  endif
2449
2450               endif
2451
2452               !!----------------------------------------------------------------------
2453               !! Fast-sinking detritus fluxes, pt. 2: UPDATE FAST FLUXES
2454               !! here locally calculated additions to the fast-sinking flux are added
2455               !! to the total fast-sinking flux; this is done here such that material
2456               !! produced in a particular layer is only remineralised below this
2457               !! layer
2458               !!----------------------------------------------------------------------
2459               !!
2460               !! add sinking material generated in this layer to running totals
2461               !!
2462               !! === organic carbon ===                          (diatom and mesozooplankton mortality)
2463               ffastc(ji,jj)  = ffastc(ji,jj)  + (ftempc(ji,jj)  * fse3t(ji,jj,jk))
2464               !!
2465               !! === organic nitrogen ===                        (diatom and mesozooplankton mortality)
2466               ffastn(ji,jj)  = ffastn(ji,jj)  + (ftempn(ji,jj)  * fse3t(ji,jj,jk))
2467               !!
2468               !! === organic iron ===                            (diatom and mesozooplankton mortality)
2469               ffastfe(ji,jj) = ffastfe(ji,jj) + (ftempfe(ji,jj) * fse3t(ji,jj,jk))
2470               !!
2471               !! === biogenic silicon ===                        (diatom mortality and grazed diatoms)
2472               ffastsi(ji,jj) = ffastsi(ji,jj) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))
2473               !!
2474               !! === biogenic calcium carbonate ===              (latitudinally-based fraction of total primary production)
2475               ffastca(ji,jj) = ffastca(ji,jj) + (ftempca(ji,jj) * fse3t(ji,jj,jk))
2476
2477               !!----------------------------------------------------------------------
2478               !! Fast-sinking detritus fluxes, pt. 3: SEAFLOOR
2479               !! remineralise all remaining fast-sinking detritus to dissolved
2480               !! nutrients; the sedimentation fluxes calculated here allow the
2481               !! separation of what's remineralised sinking through the final
2482               !! ocean box from that which is added to the final box by the
2483               !! remineralisation of material that reaches the seafloor (i.e.
2484               !! the model assumes that *all* material that hits the seafloor
2485               !! is remineralised and that none is permanently buried; hey,
2486               !! this is a giant GCM model that can't be run for long enough
2487               !! to deal with burial fluxes!)
2488               !!
2489               !! in a change to this process, in part so that MEDUSA behaves
2490               !! a little more like ERSEM et al., fast-sinking detritus (N, Fe
2491               !! and C) is converted to slow sinking detritus at the seafloor
2492               !! instead of being remineralised; the rationale is that in
2493               !! shallower shelf regions (... that are not fully mixed!) this
2494               !! allows the detrital material to return slowly to dissolved
2495               !! nutrient rather than instantaneously as now; the alternative
2496               !! would be to explicitly handle seafloor organic material - a
2497               !! headache I don't wish to experience at this point; note that
2498               !! fast-sinking Si and Ca detritus is just remineralised as
2499               !! per usual
2500               !!
2501               !! AXY (13/01/12)
2502               !! in a further change to this process, again so that MEDUSA is
2503               !! a little more like ERSEM et al., material that reaches the
2504               !! seafloor can now be added to sediment pools and stored for
2505               !! slow release; there are new 2D arrays for organic nitrogen,
2506               !! iron and carbon and inorganic silicon and carbon that allow
2507               !! fast and slow detritus that reaches the seafloor to be held
2508               !! and released back to the water column more slowly; these arrays
2509               !! are transferred via the tracer restart files between repeat
2510               !! submissions of the model
2511               !!----------------------------------------------------------------------
2512               !!
2513               ffast2slowc(ji,jj)  = 0.0
2514               ffast2slown(ji,jj)  = 0.0
2515! I don't think this is used - marc 10/4/17
2516!               ffast2slowfe(ji,jj) = 0.0
2517               !!
2518               if (jk.eq.mbathy(ji,jj)) then
2519                  !! this is the BOTTOM OCEAN BOX (remineralise everything)
2520                  !!
2521                  !! AXY (17/01/12): tweaked to include benthos pools
2522                  !!
2523                  !! === organic carbon ===
2524                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
2525                     freminc(ji,jj)  = freminc(ji,jj) + (ffastc(ji,jj) / fse3t(ji,jj,jk))    !! C remineralisation in this box            (mol/m3)
2526                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
2527                     ffast2slowc(ji,jj) = ffastc(ji,jj) / fse3t(ji,jj,jk)             !! fast C -> slow C                          (mol/m3)
2528                     fslowc(ji,jj)      = fslowc(ji,jj) + ffast2slowc(ji,jj)
2529                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
2530                     f_fbenin_c(ji,jj)  = ffastc(ji,jj)             !! fast C -> benthic C                       (mol/m2)
2531                  endif
2532                  fsedc(ji,jj)   = ffastc(ji,jj)                          !! record seafloor C                         (mol/m2)
2533                  ffastc(ji,jj)  = 0.0
2534                  !!
2535                  !! === organic nitrogen ===
2536                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
2537                     freminn(ji,jj)  = freminn(ji,jj) + (ffastn(ji,jj) / fse3t(ji,jj,jk))    !! N remineralisation in this box            (mol/m3)
2538                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
2539                     ffast2slown(ji,jj) = ffastn(ji,jj) / fse3t(ji,jj,jk)             !! fast N -> slow N                          (mol/m3)
2540                     fslown(ji,jj)      = fslown(ji,jj) + ffast2slown(ji,jj)
2541                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
2542                     f_fbenin_n(ji,jj)  = ffastn(ji,jj)             !! fast N -> benthic N                       (mol/m2)
2543                  endif
2544                  fsedn(ji,jj)   = ffastn(ji,jj)                          !! record seafloor N                         (mol/m2)
2545                  ffastn(ji,jj)  = 0.0
2546                  !!
2547                  !! === organic iron ===
2548                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
2549                     freminfe(ji,jj) = freminfe(ji,jj) + (ffastfe(ji,jj) / fse3t(ji,jj,jk))  !! Fe remineralisation in this box           (mol/m3)
2550! I don't think ffast2slowfe is used - marc 10/4/17
2551!                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
2552!                     ffast2slowfe(ji,jj) = ffastn(ji,jj) / fse3t(ji,jj,jk)            !! fast Fe -> slow Fe                        (mol/m3)
2553                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
2554                     f_fbenin_fe(ji,jj) = ffastfe(ji,jj)            !! fast Fe -> benthic Fe                     (mol/m2)
2555                  endif
2556                  fsedfe(ji,jj)  = ffastfe(ji,jj)                         !! record seafloor Fe                        (mol/m2)
2557                  ffastfe(ji,jj) = 0.0
2558                  !!
2559                  !! === biogenic silicon ===
2560                  if (jinorgben.eq.0) then
2561                     freminsi(ji,jj) = freminsi(ji,jj) + (ffastsi(ji,jj) / fse3t(ji,jj,jk))  !! Si remineralisation in this box           (mol/m3)
2562                  elseif (jinorgben.eq.1) then
2563                     f_fbenin_si(ji,jj) = ffastsi(ji,jj)            !! fast Si -> benthic Si                     (mol/m2)
2564                  endif
2565                  fsedsi(ji,jj)   = ffastsi(ji,jj)                         !! record seafloor Si                        (mol/m2)
2566                  ffastsi(ji,jj) = 0.0
2567                  !!
2568                  !! === biogenic calcium carbonate ===
2569                  if (jinorgben.eq.0) then
2570                     freminca(ji,jj) = freminca(ji,jj) + (ffastca(ji,jj) / fse3t(ji,jj,jk))  !! Ca remineralisation in this box           (mol/m3)
2571                  elseif (jinorgben.eq.1) then
2572                     f_fbenin_ca(ji,jj) = ffastca(ji,jj)            !! fast Ca -> benthic Ca                     (mol/m2)
2573                  endif
2574                  fsedca(ji,jj)   = ffastca(ji,jj)                         !! record seafloor Ca                        (mol/m2)
2575                  ffastca(ji,jj) = 0.0
2576               endif
2577
2578# if defined key_debug_medusa
2579               if (idf.eq.1) then
2580                  !!----------------------------------------------------------------------
2581                  !! Integrate total fast detritus remineralisation
2582                  !!----------------------------------------------------------------------
2583                  !!
2584                  fofd_n(ji,jj)  = fofd_n(ji,jj)  + (freminn(ji,jj)  * fse3t(ji,jj,jk))
2585                  fofd_si(ji,jj) = fofd_si(ji,jj) + (freminsi(ji,jj) * fse3t(ji,jj,jk))
2586                  fofd_fe(ji,jj) = fofd_fe(ji,jj) + (freminfe(ji,jj) * fse3t(ji,jj,jk))
2587#  if defined key_roam
2588                  fofd_c(ji,jj)  = fofd_c(ji,jj)  + (freminc(ji,jj)  * fse3t(ji,jj,jk))
2589#  endif
2590               endif
2591# endif
2592
2593               !!----------------------------------------------------------------------
2594               !! Sort out remineralisation tally of fast-sinking detritus
2595               !!----------------------------------------------------------------------
2596               !!
2597               !! update fast-sinking regeneration arrays
2598               fregenfast(ji,jj)   = fregenfast(ji,jj)   + (freminn(ji,jj)  * fse3t(ji,jj,jk))
2599               fregenfastsi(ji,jj) = fregenfastsi(ji,jj) + (freminsi(ji,jj) * fse3t(ji,jj,jk))
2600# if defined key_roam
2601               fregenfastc(ji,jj)  = fregenfastc(ji,jj)  + (freminc(ji,jj)  * fse3t(ji,jj,jk))
2602# endif
2603
2604               !!----------------------------------------------------------------------
2605               !! Benthic remineralisation fluxes
2606               !!----------------------------------------------------------------------
2607               !!
2608               if (jk.eq.mbathy(ji,jj)) then
2609                  !!
2610                  !! organic components
2611                  if (jorgben.eq.1) then
2612                     f_benout_n(ji,jj)  = xsedn  * zn_sed_n(ji,jj)
2613                     f_benout_fe(ji,jj) = xsedfe * zn_sed_fe(ji,jj)
2614                     f_benout_c(ji,jj)  = xsedc  * zn_sed_c(ji,jj)
2615                  endif
2616                  !!
2617                  !! inorganic components
2618                  if (jinorgben.eq.1) then
2619                     f_benout_si(ji,jj) = xsedsi * zn_sed_si(ji,jj)
2620                     f_benout_ca(ji,jj) = xsedca * zn_sed_ca(ji,jj)
2621                     !!
2622                     !! account for CaCO3 that dissolves when it shouldn't
2623                     if ( fsdepw(ji,jj,jk) .le. fccd_dep(ji,jj) ) then
2624                        f_benout_lyso_ca(ji,jj) = xsedca * zn_sed_ca(ji,jj)
2625                     endif
2626                  endif
2627               endif
2628               CALL flush(numout)
2629
2630               !!======================================================================
2631               !! LOCAL GRID CELL TRENDS
2632               !!======================================================================
2633               !!
2634               !!----------------------------------------------------------------------
2635               !! Determination of trends
2636               !!----------------------------------------------------------------------
2637               !!
2638               !!----------------------------------------------------------------------
2639               !! chlorophyll
2640               btra(ji,jj,jpchn) = b0 * ( &
2641                 + ((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) )
2642               btra(ji,jj,jpchd) = b0 * ( &
2643                 + ((frd(ji,jj) * fprd(ji,jj) * zphd(ji,jj)) - fgmepd(ji,jj) - fdpd(ji,jj) - fdpd2(ji,jj)) * (fthetad(ji,jj) / xxi) )
2644               !!
2645               !!----------------------------------------------------------------------
2646               !! phytoplankton
2647               btra(ji,jj,jpphn) = b0 * ( &
2648                 + (fprn(ji,jj) * zphn(ji,jj)) - fgmipn(ji,jj) - fgmepn(ji,jj) - fdpn(ji,jj) - fdpn2(ji,jj) )
2649               btra(ji,jj,jpphd) = b0 * ( &
2650                 + (fprd(ji,jj) * zphd(ji,jj)) - fgmepd(ji,jj) - fdpd(ji,jj) - fdpd2(ji,jj) )
2651               btra(ji,jj,jppds) = b0 * ( &
2652                 + (fprds(ji,jj) * zpds(ji,jj)) - fgmepds(ji,jj) - fdpds(ji,jj) - fsdiss(ji,jj) - fdpds2(ji,jj) )
2653               !!
2654               !!----------------------------------------------------------------------
2655               !! zooplankton
2656               btra(ji,jj,jpzmi) = b0 * ( &
2657                 + fmigrow(ji,jj) - fgmezmi(ji,jj) - fdzmi(ji,jj) - fdzmi2(ji,jj) )
2658               btra(ji,jj,jpzme) = b0 * ( &
2659                 + fmegrow(ji,jj) - fdzme(ji,jj) - fdzme2(ji,jj) )
2660               !!
2661               !!----------------------------------------------------------------------
2662               !! detritus
2663               btra(ji,jj,jpdet) = b0 * ( &
2664                 + fdpn(ji,jj) + ((1.0 - xfdfrac1) * fdpd(ji,jj))              &  ! mort. losses
2665                 + fdzmi(ji,jj) + ((1.0 - xfdfrac2) * fdzme(ji,jj))            &  ! mort. losses
2666                 + ((1.0 - xbetan) * (finmi(ji,jj) + finme(ji,jj)))            &  ! assim. inefficiency
2667                 - fgmid(ji,jj) - fgmed(ji,jj) - fdd(ji,jj)                           &  ! grazing and remin.
2668                 + ffast2slown(ji,jj) )                                    ! seafloor fast->slow
2669               !!
2670               !!----------------------------------------------------------------------
2671               !! dissolved inorganic nitrogen nutrient
2672               fn_cons = 0.0  &
2673                 - (fprn(ji,jj) * zphn(ji,jj)) - (fprd(ji,jj) * zphd(ji,jj))                    ! primary production
2674               fn_prod = 0.0  &
2675                 + (xphi * (fgmipn(ji,jj) + fgmid(ji,jj)))                     &  ! messy feeding remin.
2676                 + (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) + fgmezmi(ji,jj) + fgmed(ji,jj)))  &  ! messy feeding remin.
2677                 + fmiexcr(ji,jj) + fmeexcr(ji,jj) + fdd(ji,jj) + freminn(ji,jj)             &  ! excretion and remin.
2678                 + fdpn2(ji,jj) + fdpd2(ji,jj) + fdzmi2(ji,jj) + fdzme2(ji,jj)                  ! metab. losses
2679               !!
2680               !! riverine flux
2681               if ( jriver_n .gt. 0 ) then
2682                  f_riv_loc_n(ji,jj) = f_riv_n(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2683                  fn_prod = fn_prod + f_riv_loc_n(ji,jj)
2684               endif
2685               !! 
2686               !! benthic remineralisation
2687               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2688                  fn_prod = fn_prod + (f_benout_n(ji,jj) / fse3t(ji,jj,jk))
2689               endif
2690               !!
2691               btra(ji,jj,jpdin) = b0 * ( &
2692                 fn_prod + fn_cons )
2693               !!
2694               fnit_cons(ji,jj) = fnit_cons(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! consumption of dissolved nitrogen
2695                 fn_cons ) )
2696               fnit_prod(ji,jj) = fnit_prod(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! production of dissolved nitrogen
2697                 fn_prod ) )
2698               !!
2699               !!----------------------------------------------------------------------
2700               !! dissolved silicic acid nutrient
2701               fs_cons = 0.0  &
2702                 - (fprds(ji,jj) * zpds(ji,jj))                                   ! opal production
2703               fs_prod = 0.0  &
2704                 + fsdiss(ji,jj)                                        &  ! opal dissolution
2705                 + ((1.0 - xfdfrac1) * fdpds(ji,jj))                    &  ! mort. loss
2706                 + ((1.0 - xfdfrac3) * fgmepds(ji,jj))                  &  ! egestion of grazed Si
2707                 + freminsi(ji,jj) + fdpds2(ji,jj)                                ! fast diss. and metab. losses
2708               !!
2709               !! riverine flux
2710               if ( jriver_si .gt. 0 ) then
2711                  f_riv_loc_si(ji,jj) = f_riv_si(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2712                  fs_prod = fs_prod + f_riv_loc_si(ji,jj)
2713               endif
2714               !! 
2715               !! benthic remineralisation
2716               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then
2717                  fs_prod = fs_prod + (f_benout_si(ji,jj) / fse3t(ji,jj,jk))
2718               endif
2719               !!
2720               btra(ji,jj,jpsil) = b0 * ( &
2721                 fs_prod + fs_cons )
2722               !!
2723               fsil_cons(ji,jj) = fsil_cons(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! consumption of dissolved silicon
2724                 fs_cons ) )
2725               fsil_prod(ji,jj) = fsil_prod(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! production of dissolved silicon
2726                 fs_prod ) )
2727               !!
2728               !!----------------------------------------------------------------------
2729               !! dissolved "iron" nutrient
2730               btra(ji,jj,jpfer) = b0 * ( &
2731               + (xrfn * btra(ji,jj,jpdin)) + ffetop(ji,jj) + ffebot(ji,jj) - ffescav(ji,jj) )
2732
2733# if defined key_roam
2734               !!
2735               !!----------------------------------------------------------------------
2736               !! AXY (26/11/08): implicit detrital carbon change
2737               btra(ji,jj,jpdtc) = b0 * ( &
2738                 + (xthetapn * fdpn(ji,jj)) + ((1.0 - xfdfrac1) * (xthetapd * fdpd(ji,jj)))      &  ! mort. losses
2739                 + (xthetazmi * fdzmi(ji,jj)) + ((1.0 - xfdfrac2) * (xthetazme * fdzme(ji,jj)))  &  ! mort. losses
2740                 + ((1.0 - xbetac) * (ficmi(ji,jj) + ficme(ji,jj)))                              &  ! assim. inefficiency
2741                 - fgmidc(ji,jj) - fgmedc(ji,jj) - fddc(ji,jj)                                          &  ! grazing and remin.
2742                 + ffast2slowc(ji,jj) )                                                      ! seafloor fast->slow
2743               !!
2744               !!----------------------------------------------------------------------
2745               !! dissolved inorganic carbon
2746               fc_cons = 0.0  &
2747                 - (xthetapn * fprn(ji,jj) * zphn(ji,jj)) - (xthetapd * fprd(ji,jj) * zphd(ji,jj))                ! primary production
2748               fc_prod = 0.0  &
2749                 + (xthetapn * xphi * fgmipn(ji,jj)) + (xphi * fgmidc(ji,jj))                    &  ! messy feeding remin
2750                 + (xthetapn * xphi * fgmepn(ji,jj)) + (xthetapd * xphi * fgmepd(ji,jj))         &  ! messy feeding remin
2751                 + (xthetazmi * xphi * fgmezmi(ji,jj)) + (xphi * fgmedc(ji,jj))                  &  ! messy feeding remin
2752                 + fmiresp(ji,jj) + fmeresp(ji,jj) + fddc(ji,jj) + freminc(ji,jj) + (xthetapn * fdpn2(ji,jj))         &  ! resp., remin., losses
2753                 + (xthetapd * fdpd2(ji,jj)) + (xthetazmi * fdzmi2(ji,jj))                       &  ! losses
2754                 + (xthetazme * fdzme2(ji,jj))                                               ! losses
2755               !!
2756               !! riverine flux
2757               if ( jriver_c .gt. 0 ) then
2758                  f_riv_loc_c(ji,jj) = f_riv_c(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2759                  fc_prod = fc_prod + f_riv_loc_c(ji,jj)
2760               endif
2761               !! 
2762               !! benthic remineralisation
2763               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2764                  fc_prod = fc_prod + (f_benout_c(ji,jj) / fse3t(ji,jj,jk))
2765               endif
2766               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then
2767                  fc_prod = fc_prod + (f_benout_ca(ji,jj) / fse3t(ji,jj,jk))
2768               endif
2769               !!
2770               !! community respiration (does not include CaCO3 terms - obviously!)
2771               fcomm_resp(ji,jj) = fcomm_resp(ji,jj) + fc_prod
2772               !!
2773               !! CaCO3
2774               fc_prod = fc_prod - ftempca(ji,jj) + freminca(ji,jj)
2775               !!
2776               !! riverine flux
2777               if ( jk .eq. 1 .and. jriver_c .gt. 0 ) then
2778                  fc_prod = fc_prod + f_riv_c(ji,jj)
2779               endif
2780               !!
2781               btra(ji,jj,jpdic) = b0 * ( &
2782                 fc_prod + fc_cons )
2783               !!
2784               fcar_cons(ji,jj) = fcar_cons(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! consumption of dissolved carbon
2785                 fc_cons ) )
2786               fcar_prod(ji,jj) = fcar_prod(ji,jj) + ( fse3t(ji,jj,jk) * (  &  ! production of dissolved carbon
2787                 fc_prod ) )
2788               !!
2789               !!----------------------------------------------------------------------
2790               !! alkalinity
2791               fa_prod = 0.0  &
2792                 + (2.0 * freminca(ji,jj))                                                   ! CaCO3 dissolution
2793               fa_cons = 0.0  &
2794                 - (2.0 * ftempca(ji,jj))                                                    ! CaCO3 production
2795               !!
2796               !! riverine flux
2797               if ( jriver_alk .gt. 0 ) then
2798                  f_riv_loc_alk(ji,jj) = f_riv_alk(ji,jj) * friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
2799                  fa_prod = fa_prod + f_riv_loc_alk(ji,jj)
2800               endif
2801               !! 
2802               !! benthic remineralisation
2803               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then
2804                  fa_prod = fa_prod + (2.0 * f_benout_ca(ji,jj) / fse3t(ji,jj,jk))
2805               endif
2806               !!
2807               btra(ji,jj,jpalk) = b0 * ( &
2808                 fa_prod + fa_cons )
2809               !!
2810               !!----------------------------------------------------------------------
2811               !! oxygen (has protection at low O2 concentrations; OCMIP-2 style)
2812               fo2_prod(ji,jj) = 0.0 &
2813                 + (xthetanit * fprn(ji,jj) * zphn(ji,jj))                                      & ! Pn primary production, N
2814                 + (xthetanit * fprd(ji,jj) * zphd(ji,jj))                                      & ! Pd primary production, N
2815                 + (xthetarem * xthetapn * fprn(ji,jj) * zphn(ji,jj))                           & ! Pn primary production, C
2816                 + (xthetarem * xthetapd * fprd(ji,jj) * zphd(ji,jj))                             ! Pd primary production, C
2817               fo2_ncons(ji,jj) = 0.0 &
2818                 - (xthetanit * xphi * fgmipn(ji,jj))                                    & ! Pn messy feeding remin., N
2819                 - (xthetanit * xphi * fgmid(ji,jj))                                     & ! D  messy feeding remin., N
2820                 - (xthetanit * xphi * fgmepn(ji,jj))                                    & ! Pn messy feeding remin., N
2821                 - (xthetanit * xphi * fgmepd(ji,jj))                                    & ! Pd messy feeding remin., N
2822                 - (xthetanit * xphi * fgmezmi(ji,jj))                                   & ! Zi messy feeding remin., N
2823                 - (xthetanit * xphi * fgmed(ji,jj))                                     & ! D  messy feeding remin., N
2824                 - (xthetanit * fmiexcr(ji,jj))                                          & ! microzoo excretion, N
2825                 - (xthetanit * fmeexcr(ji,jj))                                          & ! mesozoo  excretion, N
2826                 - (xthetanit * fdd(ji,jj))                                              & ! slow detritus remin., N
2827                 - (xthetanit * freminn(ji,jj))                                          & ! fast detritus remin., N
2828                 - (xthetanit * fdpn2(ji,jj))                                            & ! Pn  losses, N
2829                 - (xthetanit * fdpd2(ji,jj))                                            & ! Pd  losses, N
2830                 - (xthetanit * fdzmi2(ji,jj))                                           & ! Zmi losses, N
2831                 - (xthetanit * fdzme2(ji,jj))                                             ! Zme losses, N
2832               !! 
2833               !! benthic remineralisation
2834               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2835                  fo2_ncons(ji,jj) = fo2_ncons(ji,jj) - (xthetanit * f_benout_n(ji,jj) / fse3t(ji,jj,jk))
2836               endif
2837               fo2_ccons(ji,jj) = 0.0 &
2838                 - (xthetarem * xthetapn * xphi * fgmipn(ji,jj))                         & ! Pn messy feeding remin., C
2839                 - (xthetarem * xphi * fgmidc(ji,jj))                                    & ! D  messy feeding remin., C
2840                 - (xthetarem * xthetapn * xphi * fgmepn(ji,jj))                         & ! Pn messy feeding remin., C
2841                 - (xthetarem * xthetapd * xphi * fgmepd(ji,jj))                         & ! Pd messy feeding remin., C
2842                 - (xthetarem * xthetazmi * xphi * fgmezmi(ji,jj))                       & ! Zi messy feeding remin., C
2843                 - (xthetarem * xphi * fgmedc(ji,jj))                                    & ! D  messy feeding remin., C
2844                 - (xthetarem * fmiresp(ji,jj))                                          & ! microzoo respiration, C
2845                 - (xthetarem * fmeresp(ji,jj))                                          & ! mesozoo  respiration, C
2846                 - (xthetarem * fddc(ji,jj))                                             & ! slow detritus remin., C
2847                 - (xthetarem * freminc(ji,jj))                                          & ! fast detritus remin., C
2848                 - (xthetarem * xthetapn * fdpn2(ji,jj))                                 & ! Pn  losses, C
2849                 - (xthetarem * xthetapd * fdpd2(ji,jj))                                 & ! Pd  losses, C
2850                 - (xthetarem * xthetazmi * fdzmi2(ji,jj))                               & ! Zmi losses, C
2851                 - (xthetarem * xthetazme * fdzme2(ji,jj))                                 ! Zme losses, C
2852               !! 
2853               !! benthic remineralisation
2854               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and. ibenthic.eq.1) then
2855                  fo2_ccons(ji,jj) = fo2_ccons(ji,jj) - (xthetarem * f_benout_c(ji,jj) / fse3t(ji,jj,jk))
2856               endif
2857               fo2_cons(ji,jj) = fo2_ncons(ji,jj) + fo2_ccons(ji,jj)
2858               !!
2859               !! is this a suboxic zone?
2860               if (zoxy(ji,jj).lt.xo2min) then  ! deficient O2; production fluxes only
2861                  btra(ji,jj,jpoxy) = b0 * ( &
2862                    fo2_prod(ji,jj) )
2863                  foxy_prod(ji,jj) = foxy_prod(ji,jj) + ( fse3t(ji,jj,jk) * fo2_prod(ji,jj) )
2864                  foxy_anox(ji,jj) = foxy_anox(ji,jj) + ( fse3t(ji,jj,jk) * fo2_cons(ji,jj) )
2865               else                      ! sufficient O2; production + consumption fluxes
2866                  btra(ji,jj,jpoxy) = b0 * ( &
2867                    fo2_prod(ji,jj) + fo2_cons(ji,jj) )
2868                  foxy_prod(ji,jj) = foxy_prod(ji,jj) + ( fse3t(ji,jj,jk) * fo2_prod(ji,jj) )
2869                  foxy_cons(ji,jj) = foxy_cons(ji,jj) + ( fse3t(ji,jj,jk) * fo2_cons(ji,jj) )
2870               endif
2871               !!
2872               !! air-sea fluxes (if this is the surface box)
2873               if (jk.eq.1) then
2874                  !!
2875                  !! CO2 flux
2876                  btra(ji,jj,jpdic) = btra(ji,jj,jpdic) + (b0 * f_co2flux(ji,jj))
2877                  !!
2878                  !! O2 flux (mol/m3/s -> mmol/m3/d)
2879                  btra(ji,jj,jpoxy) = btra(ji,jj,jpoxy) + (b0 * f_o2flux(ji,jj))
2880               endif
2881# endif
2882
2883# if defined key_debug_medusa
2884               !! report state variable fluxes (not including fast-sinking detritus)
2885               if (idf.eq.1.AND.idfval.eq.1) then
2886                  IF (lwp) write (numout,*) '------------------------------'
2887                  IF (lwp) write (numout,*) 'btra(ji,jj,jpchn)(',jk,')  = ', btra(ji,jj,jpchn)
2888                  IF (lwp) write (numout,*) 'btra(ji,jj,jpchd)(',jk,')  = ', btra(ji,jj,jpchd)
2889                  IF (lwp) write (numout,*) 'btra(ji,jj,jpphn)(',jk,')  = ', btra(ji,jj,jpphn)
2890                  IF (lwp) write (numout,*) 'btra(ji,jj,jpphd)(',jk,')  = ', btra(ji,jj,jpphd)
2891                  IF (lwp) write (numout,*) 'btra(ji,jj,jppds)(',jk,')  = ', btra(ji,jj,jppds)
2892                  IF (lwp) write (numout,*) 'btra(ji,jj,jpzmi)(',jk,')  = ', btra(ji,jj,jpzmi)
2893                  IF (lwp) write (numout,*) 'btra(ji,jj,jpzme)(',jk,')  = ', btra(ji,jj,jpzme)
2894                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdet)(',jk,')  = ', btra(ji,jj,jpdet)
2895                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdin)(',jk,')  = ', btra(ji,jj,jpdin)
2896                  IF (lwp) write (numout,*) 'btra(ji,jj,jpsil)(',jk,')  = ', btra(ji,jj,jpsil)
2897                  IF (lwp) write (numout,*) 'btra(ji,jj,jpfer)(',jk,')  = ', btra(ji,jj,jpfer)
2898#  if defined key_roam
2899                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdtc)(',jk,')  = ', btra(ji,jj,jpdtc)
2900                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdic)(',jk,')  = ', btra(ji,jj,jpdic)
2901                  IF (lwp) write (numout,*) 'btra(ji,jj,jpalk)(',jk,')  = ', btra(ji,jj,jpalk)
2902                  IF (lwp) write (numout,*) 'btra(ji,jj,jpoxy)(',jk,')  = ', btra(ji,jj,jpoxy)
2903#  endif
2904               endif
2905# endif
2906
2907               !!----------------------------------------------------------------------
2908               !! Integrate calculated fluxes for mass balance
2909               !!----------------------------------------------------------------------
2910               !!
2911               !! === nitrogen ===
2912               fflx_n(ji,jj)  = fflx_n(ji,jj)  + &
2913                  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) )
2914               !! === silicon ===
2915               fflx_si(ji,jj) = fflx_si(ji,jj) + &
2916                  fse3t(ji,jj,jk) * ( btra(ji,jj,jppds) + btra(ji,jj,jpsil) )
2917               !! === iron ===
2918               fflx_fe(ji,jj) = fflx_fe(ji,jj) + &
2919                  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) )
2920# if defined key_roam
2921               !! === carbon ===
2922               fflx_c(ji,jj)  = fflx_c(ji,jj)  + &
2923                  fse3t(ji,jj,jk) * ( (xthetapn * btra(ji,jj,jpphn)) + (xthetapd * btra(ji,jj,jpphd)) + &
2924                  (xthetazmi * btra(ji,jj,jpzmi)) + (xthetazme * btra(ji,jj,jpzme)) + btra(ji,jj,jpdtc) + btra(ji,jj,jpdic) )
2925               !! === alkalinity ===
2926               fflx_a(ji,jj)  = fflx_a(ji,jj)  + &
2927                  fse3t(ji,jj,jk) * ( btra(ji,jj,jpalk) )
2928               !! === oxygen ===
2929               fflx_o2(ji,jj) = fflx_o2(ji,jj) + &
2930                  fse3t(ji,jj,jk) * ( btra(ji,jj,jpoxy) )
2931# endif
2932
2933               !!----------------------------------------------------------------------
2934               !! Apply calculated tracer fluxes
2935               !!----------------------------------------------------------------------
2936               !!
2937               !! units: [unit of tracer] per second (fluxes are calculated above per day)
2938               !!
2939               ibio_switch = 1
2940# if defined key_gulf_finland
2941               !! AXY (17/05/13): fudge in a Gulf of Finland correction; uses longitude-
2942               !!                 latitude range to establish if this is a Gulf of Finland
2943               !!                 grid cell; if so, then BGC fluxes are ignored (though
2944               !!                 still calculated); for reference, this is meant to be a
2945               !!                 temporary fix to see if all of my problems can be done
2946               !!                 away with if I switch off BGC fluxes in the Gulf of
2947               !!                 Finland, which currently appears the source of trouble
2948               if ( glamt(ji,jj).gt.24.7 .and. glamt(ji,jj).lt.27.8 .and. &
2949                  &   gphit(ji,jj).gt.59.2 .and. gphit(ji,jj).lt.60.2 ) then
2950                  ibio_switch = 0
2951               endif
2952# endif               
2953               if (ibio_switch.eq.1) then
2954                  tra(ji,jj,jk,jpchn) = tra(ji,jj,jk,jpchn) + (btra(ji,jj,jpchn) / 86400.)
2955                  tra(ji,jj,jk,jpchd) = tra(ji,jj,jk,jpchd) + (btra(ji,jj,jpchd) / 86400.)
2956                  tra(ji,jj,jk,jpphn) = tra(ji,jj,jk,jpphn) + (btra(ji,jj,jpphn) / 86400.)
2957                  tra(ji,jj,jk,jpphd) = tra(ji,jj,jk,jpphd) + (btra(ji,jj,jpphd) / 86400.)
2958                  tra(ji,jj,jk,jppds) = tra(ji,jj,jk,jppds) + (btra(ji,jj,jppds) / 86400.)
2959                  tra(ji,jj,jk,jpzmi) = tra(ji,jj,jk,jpzmi) + (btra(ji,jj,jpzmi) / 86400.)
2960                  tra(ji,jj,jk,jpzme) = tra(ji,jj,jk,jpzme) + (btra(ji,jj,jpzme) / 86400.)
2961                  tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) + (btra(ji,jj,jpdet) / 86400.)
2962                  tra(ji,jj,jk,jpdin) = tra(ji,jj,jk,jpdin) + (btra(ji,jj,jpdin) / 86400.)
2963                  tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) + (btra(ji,jj,jpsil) / 86400.)
2964                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + (btra(ji,jj,jpfer) / 86400.)
2965# if defined key_roam
2966                  tra(ji,jj,jk,jpdtc) = tra(ji,jj,jk,jpdtc) + (btra(ji,jj,jpdtc) / 86400.)
2967                  tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) + (btra(ji,jj,jpdic) / 86400.)
2968                  tra(ji,jj,jk,jpalk) = tra(ji,jj,jk,jpalk) + (btra(ji,jj,jpalk) / 86400.)
2969                  tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) + (btra(ji,jj,jpoxy) / 86400.)
2970# endif
2971               endif               
2972
2973               !! AXY (18/11/16): CMIP6 diagnostics
2974               IF( med_diag%FBDDTALK%dgsave )  THEN
2975                  fbddtalk(ji,jj)  =  fbddtalk(ji,jj)  + (btra(ji,jj,jpalk) * fse3t(ji,jj,jk))
2976               ENDIF
2977               IF( med_diag%FBDDTDIC%dgsave )  THEN
2978                  fbddtdic(ji,jj)  =  fbddtdic(ji,jj)  + (btra(ji,jj,jpdic) * fse3t(ji,jj,jk))
2979               ENDIF
2980               IF( med_diag%FBDDTDIFE%dgsave ) THEN
2981                  fbddtdife(ji,jj) =  fbddtdife(ji,jj) + (btra(ji,jj,jpfer) * fse3t(ji,jj,jk))
2982               ENDIF
2983               IF( med_diag%FBDDTDIN%dgsave )  THEN
2984                  fbddtdin(ji,jj)  =  fbddtdin(ji,jj)  + (btra(ji,jj,jpdin) * fse3t(ji,jj,jk))
2985               ENDIF
2986               IF( med_diag%FBDDTDISI%dgsave ) THEN
2987                  fbddtdisi(ji,jj) =  fbddtdisi(ji,jj) + (btra(ji,jj,jpsil) * fse3t(ji,jj,jk))
2988               ENDIF
2989          !!
2990               IF( med_diag%BDDTALK3%dgsave )  THEN
2991                  bddtalk3(ji,jj,jk)  =  btra(ji,jj,jpalk)
2992               ENDIF
2993               IF( med_diag%BDDTDIC3%dgsave )  THEN
2994                  bddtdic3(ji,jj,jk)  =  btra(ji,jj,jpdic)
2995               ENDIF
2996               IF( med_diag%BDDTDIFE3%dgsave ) THEN
2997                  bddtdife3(ji,jj,jk) =  btra(ji,jj,jpfer)
2998               ENDIF
2999               IF( med_diag%BDDTDIN3%dgsave )  THEN
3000                  bddtdin3(ji,jj,jk)  =  btra(ji,jj,jpdin)
3001               ENDIF
3002               IF( med_diag%BDDTDISI3%dgsave ) THEN
3003                  bddtdisi3(ji,jj,jk) =  btra(ji,jj,jpsil)
3004               ENDIF
3005
3006#   if defined key_debug_medusa
3007               IF (lwp) write (numout,*) '------'
3008               IF (lwp) write (numout,*) 'trc_bio_medusa: end all calculations'
3009               IF (lwp) write (numout,*) 'trc_bio_medusa: now outputs'
3010                     CALL flush(numout)
3011#   endif
3012
3013# if defined key_axy_nancheck
3014               !!----------------------------------------------------------------------
3015               !! Check calculated tracer fluxes
3016               !!----------------------------------------------------------------------
3017               !!
3018               DO jn = 1,jptra
3019                  fq0 = btra(ji,jj,jn)
3020                  !! AXY (30/01/14): "isnan" problem on HECTOR
3021                  !! if (fq0 /= fq0 ) then
3022                  if ( ieee_is_nan( fq0 ) ) then
3023                     !! there's a NaN here
3024                     if (lwp) write(numout,*) 'NAN detected in btra(ji,jj,', ji, ',', &
3025                     & jj, ',', jk, ',', jn, ') at time', kt
3026           CALL ctl_stop( 'trcbio_medusa, NAN in btra field' )
3027                  endif
3028               ENDDO
3029               DO jn = 1,jptra
3030                  fq0 = tra(ji,jj,jk,jn)
3031                  !! AXY (30/01/14): "isnan" problem on HECTOR
3032                  !! if (fq0 /= fq0 ) then
3033                  if ( ieee_is_nan( fq0 ) ) then
3034                     !! there's a NaN here
3035                     if (lwp) write(numout,*) 'NAN detected in tra(', ji, ',', &
3036                     & jj, ',', jk, ',', jn, ') at time', kt
3037              CALL ctl_stop( 'trcbio_medusa, NAN in tra field' )
3038                  endif
3039               ENDDO
3040               CALL flush(numout)
3041# endif
3042
3043               !!----------------------------------------------------------------------
3044               !! Check model conservation
3045               !! these terms merely sum up the tendency terms of the relevant
3046               !! state variables, which should sum to zero; the iron cycle is
3047               !! complicated by fluxes that add (aeolian deposition and seafloor
3048               !! remineralisation) and remove (scavenging) dissolved iron from
3049               !! the model (i.e. the sum of iron fluxes is unlikely to be zero)
3050               !!----------------------------------------------------------------------
3051               !!
3052               !! 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)
3053               !! fsil0 = btra(ji,jj,jppds) + btra(ji,jj,jpsil)                              ! + ftempsi(ji,jj)
3054               !! ffer0 = (xrfn * fnit0) + btra(ji,jj,jpfer)
3055# if defined key_roam
3056               !! fcar0 = 0.
3057               !! falk0 = 0.
3058               !! foxy0 = 0.
3059# endif
3060               !!
3061               !! if (kt/240*240.eq.kt) then
3062               !!    if (ji.eq.2.and.jj.eq.2.and.jk.eq.1) then
3063               !!       IF (lwp) write (*,*) '*******!MEDUSA Conservation!*******',kt
3064# if defined key_roam
3065               !!       IF (lwp) write (*,*) fnit0,fsil0,ffer0,fcar0,falk0,foxy0
3066# else
3067               !!       IF (lwp) write (*,*) fnit0,fsil0,ffer0
3068# endif
3069               !!    endif
3070               !! endif     
3071
3072# if defined key_trc_diabio
3073               !!======================================================================
3074               !! LOCAL GRID CELL DIAGNOSTICS
3075               !!======================================================================
3076               !!
3077               !!----------------------------------------------------------------------
3078               !! Full diagnostics key_trc_diabio:
3079               !! LOBSTER and PISCES support full diagnistics option key_trc_diabio   
3080               !! which gives an option of FULL output of biological sourses and sinks.
3081               !! I cannot see any reason for doing this. If needed, it can be done
3082               !! as shown below.
3083               !!----------------------------------------------------------------------
3084               !!
3085               IF(lwp) WRITE(numout,*) ' MEDUSA does not support key_trc_diabio'
3086               !!               trbio(ji,jj,jk, 1) = fprn(ji,jj)
3087# endif
3088
3089               IF( lk_iomput  .AND.  .NOT.  ln_diatrc  ) THEN
3090         !!----------------------------------------------------------------------
3091         !! Add in XML diagnostics stuff
3092         !!----------------------------------------------------------------------
3093         !!
3094         !! ** 2D diagnostics
3095#   if defined key_debug_medusa
3096                  IF (lwp) write (numout,*) 'trc_bio_medusa: diag in ij-jj-jk loop'
3097                  CALL flush(numout)
3098#   endif
3099                  IF ( med_diag%PRN%dgsave ) THEN
3100                      fprn2d(ji,jj) = fprn2d(ji,jj) + (fprn(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3101                  ENDIF
3102                  IF ( med_diag%MPN%dgsave ) THEN
3103                      fdpn2d(ji,jj) = fdpn2d(ji,jj) + (fdpn(ji,jj)         * fse3t(ji,jj,jk))
3104                  ENDIF
3105                  IF ( med_diag%PRD%dgsave ) THEN
3106                      fprd2d(ji,jj) = fprd2d(ji,jj) + (fprd(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))
3107                  ENDIF
3108                  IF( med_diag%MPD%dgsave ) THEN
3109                      fdpd2d(ji,jj) = fdpd2d(ji,jj) + (fdpd(ji,jj)         * fse3t(ji,jj,jk)) 
3110                  ENDIF
3111                  !  IF( med_diag%DSED%dgsave ) THEN
3112                  !      CALL iom_put( "DSED"  , ftot_n )
3113                  !  ENDIF
3114                  IF( med_diag%OPAL%dgsave ) THEN
3115                      fprds2d(ji,jj) = fprds2d(ji,jj) + (fprds(ji,jj) * zpds(ji,jj) * fse3t(ji,jj,jk)) 
3116                  ENDIF
3117                  IF( med_diag%OPALDISS%dgsave ) THEN
3118                      fsdiss2d(ji,jj) = fsdiss2d(ji,jj) + (fsdiss(ji,jj)  * fse3t(ji,jj,jk)) 
3119                  ENDIF
3120                  IF( med_diag%GMIPn%dgsave ) THEN
3121                      fgmipn2d(ji,jj) = fgmipn2d(ji,jj) + (fgmipn(ji,jj)  * fse3t(ji,jj,jk)) 
3122                  ENDIF
3123                  IF( med_diag%GMID%dgsave ) THEN
3124                      fgmid2d(ji,jj) = fgmid2d(ji,jj) + (fgmid(ji,jj)   * fse3t(ji,jj,jk)) 
3125                  ENDIF
3126                  IF( med_diag%MZMI%dgsave ) THEN
3127                      fdzmi2d(ji,jj) = fdzmi2d(ji,jj) + (fdzmi(ji,jj)   * fse3t(ji,jj,jk)) 
3128                  ENDIF
3129                  IF( med_diag%GMEPN%dgsave ) THEN
3130                      fgmepn2d(ji,jj) = fgmepn2d(ji,jj) + (fgmepn(ji,jj)  * fse3t(ji,jj,jk))
3131                  ENDIF
3132                  IF( med_diag%GMEPD%dgsave ) THEN
3133                      fgmepd2d(ji,jj) = fgmepd2d(ji,jj) + (fgmepd(ji,jj)  * fse3t(ji,jj,jk)) 
3134                  ENDIF
3135                  IF( med_diag%GMEZMI%dgsave ) THEN
3136                      fgmezmi2d(ji,jj) = fgmezmi2d(ji,jj) + (fgmezmi(ji,jj) * fse3t(ji,jj,jk)) 
3137                  ENDIF
3138                  IF( med_diag%GMED%dgsave ) THEN
3139                      fgmed2d(ji,jj) = fgmed2d(ji,jj) + (fgmed(ji,jj)   * fse3t(ji,jj,jk)) 
3140                  ENDIF
3141                  IF( med_diag%MZME%dgsave ) THEN
3142                      fdzme2d(ji,jj) = fdzme2d(ji,jj) + (fdzme(ji,jj)   * fse3t(ji,jj,jk)) 
3143                  ENDIF
3144                  !  IF( med_diag%DEXP%dgsave ) THEN
3145                  !      CALL iom_put( "DEXP"  , ftot_n )
3146                  !  ENDIF
3147                  IF( med_diag%DETN%dgsave ) THEN
3148                      fslown2d(ji,jj) = fslown2d(ji,jj) + (fslown(ji,jj)  * fse3t(ji,jj,jk)) 
3149                  ENDIF
3150                  IF( med_diag%MDET%dgsave ) THEN
3151                      fdd2d(ji,jj) = fdd2d(ji,jj) + (fdd(ji,jj)     * fse3t(ji,jj,jk)) 
3152                  ENDIF
3153                  IF( med_diag%AEOLIAN%dgsave ) THEN
3154                      ffetop2d(ji,jj) = ffetop2d(ji,jj) + (ffetop(ji,jj)  * fse3t(ji,jj,jk)) 
3155                  ENDIF
3156                  IF( med_diag%BENTHIC%dgsave ) THEN
3157                      ffebot2d(ji,jj) = ffebot2d(ji,jj) + (ffebot(ji,jj)  * fse3t(ji,jj,jk)) 
3158                  ENDIF
3159                  IF( med_diag%SCAVENGE%dgsave ) THEN
3160                      ffescav2d(ji,jj) = ffescav2d(ji,jj) + (ffescav(ji,jj) * fse3t(ji,jj,jk)) 
3161                  ENDIF
3162                  IF( med_diag%PN_JLIM%dgsave ) THEN
3163                      ! fjln2d(ji,jj) = fjln2d(ji,jj) + (fjln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk))
3164                      fjln2d(ji,jj) = fjln2d(ji,jj) + (fjlim_pn(ji,jj) * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3165                  ENDIF
3166                  IF( med_diag%PN_NLIM%dgsave ) THEN
3167                      fnln2d(ji,jj) = fnln2d(ji,jj) + (fnln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3168                  ENDIF
3169                  IF( med_diag%PN_FELIM%dgsave ) THEN
3170                      ffln2d(ji,jj) = ffln2d(ji,jj) + (ffln(ji,jj)  * zphn(ji,jj) * fse3t(ji,jj,jk)) 
3171                  ENDIF
3172                  IF( med_diag%PD_JLIM%dgsave ) THEN
3173                      ! fjld2d(ji,jj) = fjld2d(ji,jj) + (fjld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))
3174                      fjld2d(ji,jj) = fjld2d(ji,jj) + (fjlim_pd(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3175                  ENDIF
3176                  IF( med_diag%PD_NLIM%dgsave ) THEN
3177                      fnld2d(ji,jj) = fnld2d(ji,jj) + (fnld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3178                  ENDIF
3179                  IF( med_diag%PD_FELIM%dgsave ) THEN
3180                      ffld2d(ji,jj) = ffld2d(ji,jj) + (ffld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3181                  ENDIF
3182                  IF( med_diag%PD_SILIM%dgsave ) THEN
3183                      fsld2d2(ji,jj) = fsld2d2(ji,jj) + (fsld2(ji,jj) * zphd(ji,jj) * fse3t(ji,jj,jk)) 
3184                  ENDIF
3185                  IF( med_diag%PDSILIM2%dgsave ) THEN
3186                      fsld2d(ji,jj) = fsld2d(ji,jj) + (fsld(ji,jj)  * zphd(ji,jj) * fse3t(ji,jj,jk))
3187                  ENDIF
3188                  !!
3189                  IF( med_diag%TOTREG_N%dgsave ) THEN
3190                      fregen2d(ji,jj) = fregen2d(ji,jj) + fregen(ji,jj)
3191                  ENDIF
3192                  IF( med_diag%TOTRG_SI%dgsave ) THEN
3193                      fregensi2d(ji,jj) = fregensi2d(ji,jj) + fregensi(ji,jj)
3194                  ENDIF
3195                  !!
3196                  IF( med_diag%FASTN%dgsave ) THEN
3197                      ftempn2d(ji,jj) = ftempn2d(ji,jj) + (ftempn(ji,jj)  * fse3t(ji,jj,jk))
3198                  ENDIF
3199                  IF( med_diag%FASTSI%dgsave ) THEN
3200                      ftempsi2d(ji,jj) = ftempsi2d(ji,jj) + (ftempsi(ji,jj) * fse3t(ji,jj,jk))
3201                  ENDIF
3202                  IF( med_diag%FASTFE%dgsave ) THEN
3203                      ftempfe2d(ji,jj) =ftempfe2d(ji,jj)  + (ftempfe(ji,jj) * fse3t(ji,jj,jk)) 
3204                  ENDIF
3205                  IF( med_diag%FASTC%dgsave ) THEN
3206                      ftempc2d(ji,jj) = ftempc2d(ji,jj) + (ftempc(ji,jj)  * fse3t(ji,jj,jk))
3207                  ENDIF
3208                  IF( med_diag%FASTCA%dgsave ) THEN
3209                      ftempca2d(ji,jj) = ftempca2d(ji,jj) + (ftempca(ji,jj) * fse3t(ji,jj,jk))
3210                  ENDIF
3211                  !!
3212                  IF( med_diag%REMINN%dgsave ) THEN
3213                      freminn2d(ji,jj) = freminn2d(ji,jj) + (freminn(ji,jj)  * fse3t(ji,jj,jk))
3214                  ENDIF
3215                  IF( med_diag%REMINSI%dgsave ) THEN
3216                      freminsi2d(ji,jj) = freminsi2d(ji,jj) + (freminsi(ji,jj) * fse3t(ji,jj,jk))
3217                  ENDIF
3218                  IF( med_diag%REMINFE%dgsave ) THEN
3219                      freminfe2d(ji,jj)= freminfe2d(ji,jj) + (freminfe(ji,jj) * fse3t(ji,jj,jk)) 
3220                  ENDIF
3221                  IF( med_diag%REMINC%dgsave ) THEN
3222                      freminc2d(ji,jj) = freminc2d(ji,jj) + (freminc(ji,jj)  * fse3t(ji,jj,jk)) 
3223                  ENDIF
3224                  IF( med_diag%REMINCA%dgsave ) THEN
3225                      freminca2d(ji,jj) = freminca2d(ji,jj) + (freminca(ji,jj) * fse3t(ji,jj,jk)) 
3226                  ENDIF
3227                  !!
3228# if defined key_roam
3229                  !!
3230                  !! AXY (09/11/16): CMIP6 diagnostics
3231                  IF( med_diag%FD_NIT3%dgsave ) THEN
3232                     fd_nit3(ji,jj,jk) = ffastn(ji,jj)
3233                  ENDIF
3234                  IF( med_diag%FD_SIL3%dgsave ) THEN
3235                     fd_sil3(ji,jj,jk) = ffastsi(ji,jj)
3236                  ENDIF
3237                  IF( med_diag%FD_CAR3%dgsave ) THEN
3238                     fd_car3(ji,jj,jk) = ffastc(ji,jj)
3239                  ENDIF
3240                  IF( med_diag%FD_CAL3%dgsave ) THEN
3241                     fd_cal3(ji,jj,jk) = ffastca(ji,jj)
3242                  ENDIF
3243                  !!
3244                  IF (jk.eq.i0100) THEN
3245                     IF( med_diag%RR_0100%dgsave ) THEN
3246                        ffastca2d(ji,jj) =   &
3247                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)
3248                     ENDIF                     
3249                  ELSE IF (jk.eq.i0500) THEN
3250                     IF( med_diag%RR_0500%dgsave ) THEN
3251                        ffastca2d(ji,jj) =   &
3252                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)
3253                     ENDIF                       
3254                  ELSE IF (jk.eq.i1000) THEN
3255                     IF( med_diag%RR_1000%dgsave ) THEN
3256                        ffastca2d(ji,jj) =   &
3257                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)
3258                     ENDIF
3259                  ELSE IF (jk.eq.mbathy(ji,jj)) THEN
3260                     IF( med_diag%IBEN_N%dgsave ) THEN
3261                        iben_n2d(ji,jj) = f_sbenin_n(ji,jj)  + f_fbenin_n(ji,jj)
3262                     ENDIF
3263                     IF( med_diag%IBEN_FE%dgsave ) THEN