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

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

Removed plankton processes from trcbio_medusa.F90 into extra routines

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