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

source: branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/TOP_SRC/MEDUSA/detritus_fast_sink.F90 @ 10196

Last change on this file since 10196 was 10196, checked in by jpalmier, 6 years ago

add DMS flux --

File size: 52.3 KB
Line 
1MODULE detritus_fast_sink_mod
2   !!======================================================================
3   !!                         ***  MODULE detritus_fast_sink_mod  ***
4   !! Calculates fast-sinking detritus processes (plus other diagnostics)
5   !!======================================================================
6   !! History :
7   !!   -   ! 2017-04 (M. Stringer)        Code taken from trcbio_medusa.F90
8   !!   -   ! 2018-19 (A. Yool)            Bugfix for excessive CaCO3 production
9   !!----------------------------------------------------------------------
10#if defined key_medusa
11   !!----------------------------------------------------------------------
12   !!                                                   MEDUSA bio-model
13   !!----------------------------------------------------------------------
14
15   IMPLICIT NONE
16   PRIVATE
17     
18   PUBLIC   detritus_fast_sink        ! Called in detritus.F90
19
20   !!----------------------------------------------------------------------
21   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
22   !! $Id$
23   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
24   !!----------------------------------------------------------------------
25
26CONTAINS
27
28   SUBROUTINE detritus_fast_sink( jk, iball )
29      !!-------------------------------------------------------------------
30      !!                     ***  ROUTINE detritus_fast_sink  ***
31      !! This called from DETRITUS and calculates the fast-sinking detritus
32      !!-------------------------------------------------------------------
33      USE bio_medusa_mod,    ONLY: b0,                                     &
34                                   f_benout_c, f_benout_ca, f_benout_fe,   &
35                                   f_benout_lyso_ca, f_benout_n,           &
36                                   f_benout_si,                            &
37                                   f_fbenin_c, f_fbenin_ca, f_fbenin_fe,   &
38                                   f_fbenin_n, f_fbenin_si, f_omcal,       &
39                                   fccd, fdep1, fdd,                       &
40                                   fdpd, fdpd2, fdpds, fdpds2,             &
41                                   fdpn, fdpn2,                            &
42                                   fdzme, fdzme2, fdzmi, fdzmi2,           &
43                                   ffast2slowc, ffast2slown,               &
44                                   ffastc, ffastca, ffastfe, ffastn,       &
45                                   ffastsi,                                &
46                                   fgmed, fgmepd, fgmepds, fgmepn,         &
47                                   fgmezmi,                                &
48                                   fgmid, fgmipn,                          &
49                                   ficme, ficmi,                           &
50                                   fifd_fe, fifd_n, fifd_si,               &
51                                   finme, finmi,                           &
52                                   fmeexcr, fmiexcr,                       &
53                                   fofd_fe, fofd_n, fofd_si,               &
54                                   fregen, fregenfast, fregenfastsi,       &
55                                   fregensi,                               &
56                                   freminc, freminca, freminfe,            &
57                                   freminn, freminsi,                      &
58                                   fsdiss,                                 &
59                                   fsedc, fsedca, fsedn, fsedfe, fsedsi,   &
60                                   fslowc, fslowcflux,                     &
61                                   fslown, fslownflux,                     &
62                                   ftempc, ftempca, ftempfe, ftempn,       &
63                                   ftempsi,                                &
64# if defined key_roam
65                                   fifd_c, fofd_c, fregenfastc,            &
66               zdic, zalk,                             & 
67# endif
68                                   idf, idfval,                            &
69                                   zdet, zdtc
70      USE dom_oce,           ONLY: e3t_0, gdepw_0, gphit, mbathy, tmask
71# if defined key_vvl
72      USE dom_oce,           ONLY: e3t_n, gdepw_n
73# endif
74      USE in_out_manager,    ONLY: lwp, numout
75      USE oce,               ONLY: tsn
76      USE par_kind,          ONLY: wp
77      USE par_oce,           ONLY: jpi, jpim1, jpj, jpjm1
78      USE sms_medusa,        ONLY: f2_ccd_cal, f3_omcal,                   &
79                                   jexport, jfdfate, jinorgben, jocalccd,  &
80                                   jorgben, jp_tem, jrratio,               &
81                                   ocal_ccd, vsed,                         &
82                                   xbetac, xbetan,                         &
83                                   xcaco3a, xcaco3b,                       &
84                                   xfastc, xfastca, xfastsi,               &
85                                   xfdfrac1, xfdfrac2, xfdfrac3,           &
86                                   xmassc, xmassca, xmasssi,               &
87                                   xphi, xprotca, xprotsi,                 &
88                                   xrfn, xridg_r0,                         &
89                                   xsedc, xsedca, xsedfe,xsedn, xsedsi,    &
90                                   xthetapd, xthetapn,                     &
91                                   xthetazme, xthetazmi,                   &
92                                   zn_sed_c, zn_sed_ca, zn_sed_fe,         &
93                                   zn_sed_n, zn_sed_si
94
95   !!* Substitution
96#  include "domzgr_substitute.h90"
97
98      !! Level
99      INTEGER, INTENT( in ) :: jk
100      !! Fast detritus ballast scheme (0 = no; 1 = yes)
101      INTEGER, INTENT( in ) :: iball
102
103      !! Loop variables
104      INTEGER :: ji, jj
105
106      REAL(wp) :: fb_val, fl_sst
107      !! Particle flux
108      REAL(wp) :: fcaco3
109      REAL(wp) :: fprotf
110      REAL(wp), DIMENSION(jpi,jpj) :: fccd_dep
111      !! temporary variables
112      REAL(wp) :: fq0,fq1,fq2,fq3,fq4,fq5,fq6,fq7,fq8
113
114      !! The two sections below, slow detritus creation and Nutrient
115      !! regeneration are moved from just above the CALL to DETRITUS
116      !! in trcbio_medusa.F90.
117      !!---------------------------------------------------------
118      !! Slow detritus creation
119      !!---------------------------------------------------------
120      DO jj = 2,jpjm1
121         DO ji = 2,jpim1
122            IF (tmask(ji,jj,jk) == 1) THEN
123               !!
124               !! this variable integrates the creation of slow sinking
125               !! detritus to allow the split between fast and slow
126               !! detritus to be diagnosed
127               fslown(ji,jj)  = fdpn(ji,jj) + fdzmi(ji,jj) +                 &
128                                ((1.0 - xfdfrac1) * fdpd(ji,jj)) +           &
129                                ((1.0 - xfdfrac2) * fdzme(ji,jj)) +          &
130                                ((1.0 - xbetan) *                            &
131                                 (finmi(ji,jj) + finme(ji,jj)))
132               !!
133               !! this variable records the slow detrital sinking flux at
134               !! this particular depth; it is used in the output of this
135               !! flux at standard depths in the diagnostic outputs;
136               !! needs to be adjusted from per second to per day because
137               !! of parameter vsed
138               fslownflux(ji,jj) = zdet(ji,jj) * vsed * 86400.
139# if defined key_roam
140               !!
141               !! and the same for detrital carbon
142               fslowc(ji,jj)  = (xthetapn * fdpn(ji,jj)) +                   &
143                                (xthetazmi * fdzmi(ji,jj)) +                 &
144                                (xthetapd * (1.0 - xfdfrac1) *               &
145                                 fdpd(ji,jj)) +                              &
146                                (xthetazme * (1.0 - xfdfrac2) *              &
147                                 fdzme(ji,jj)) +                             &
148                                ((1.0 - xbetac) * (ficmi(ji,jj) +            &
149                                                   ficme(ji,jj)))
150               !!
151               !! this variable records the slow detrital sinking flux
152               !! at this particular depth; it is used in the output of
153               !! this flux at standard depths in the diagnostic
154               !! outputs; needs to be adjusted from per second to per
155               !! day because of parameter vsed
156               fslowcflux(ji,jj) = zdtc(ji,jj) * vsed * 86400.
157# endif
158            ENDIF
159         ENDDO
160      ENDDO
161
162      !!---------------------------------------------------------
163      !! Nutrient regeneration
164      !! this variable integrates total nitrogen regeneration down the
165      !! watercolumn; its value is stored and output as a 2D diagnostic;
166      !! the corresponding dissolution flux of silicon (from sources
167      !! other than fast detritus) is also integrated; note that,
168      !! confusingly, the linear loss terms from plankton compartments
169      !! are labelled as fdX2 when one might have expected fdX or fdX1
170      !!---------------------------------------------------------
171      DO jj = 2,jpjm1
172         DO ji = 2,jpim1
173            IF (tmask(ji,jj,jk) == 1) THEN
174               !!
175               !! nitrogen
176               fregen(ji,jj) =                                             &
177                                     ! messy feeding
178                               (((xphi * (fgmipn(ji,jj) + fgmid(ji,jj))) + &
179                                 (xphi *                                   &
180                                  (fgmepn(ji,jj) + fgmepd(ji,jj) +         &
181                                   fgmezmi(ji,jj) + fgmed(ji,jj))) +       &
182                                     ! excretion + D remin.
183                                 fmiexcr(ji,jj) + fmeexcr(ji,jj) +         &
184                                 fdd(ji,jj) +                              &
185                                     ! linear mortality
186                                 fdpn2(ji,jj) + fdpd2(ji,jj) +             &
187                                 fdzmi2(ji,jj) + fdzme2(ji,jj)) *          &
188                                fse3t(ji,jj,jk))
189               !!
190               !! silicon
191               fregensi(ji,jj) =                                           &
192                                     ! dissolution + non-lin. mortality
193                                 ((fsdiss(ji,jj) +                         &
194                                   ((1.0 - xfdfrac1) * fdpds(ji,jj)) +     &
195                                     ! egestion by zooplankton
196                                   ((1.0 - xfdfrac3) * fgmepds(ji,jj)) +   &
197                                     ! linear mortality
198                                   fdpds2(ji,jj)) * fse3t(ji,jj,jk))
199            ENDIF
200         ENDDO
201      ENDDO
202
203      !!-------------------------------------------------------------------
204      !! Fast-sinking detritus terms
205      !! "local" variables declared so that conservation can be checked;
206      !! the calculated terms are added to the fast-sinking flux later on
207      !! only after the flux entering this level has experienced some
208      !! remineralisation
209      !! note: these fluxes need to be scaled by the level thickness
210      !!-------------------------------------------------------------------
211      DO jj = 2,jpjm1
212         DO ji = 2,jpim1
213            !! OPEN wet point IF..THEN loop
214            if (tmask(ji,jj,jk) == 1) then
215
216               !! nitrogen:   diatom and mesozooplankton mortality
217               ftempn(ji,jj)  = b0 * ((xfdfrac1 * fdpd(ji,jj))  +            &
218                                      (xfdfrac2 * fdzme(ji,jj)))
219               !!
220               !! silicon:    diatom mortality and grazed diatoms
221               ftempsi(ji,jj) = b0 * ((xfdfrac1 * fdpds(ji,jj)) +            &
222                                      (xfdfrac3 * fgmepds(ji,jj)))
223               !!
224               !! iron:       diatom and mesozooplankton mortality
225               ftempfe(ji,jj) = b0 * (((xfdfrac1 * fdpd(ji,jj)) +            &
226                                       (xfdfrac2 * fdzme(ji,jj))) * xrfn)
227               !!
228               !! carbon:     diatom and mesozooplankton mortality
229               ftempc(ji,jj)  = b0 * ((xfdfrac1 * xthetapd * fdpd(ji,jj)) +  & 
230                                      (xfdfrac2 * xthetazme * fdzme(ji,jj)))
231               !!
232            ENDIF
233         ENDDO
234      ENDDO
235
236# if defined key_roam
237      DO jj = 2,jpjm1
238         DO ji = 2,jpim1
239            if (tmask(ji,jj,jk) == 1) then
240               if (jrratio.eq.0) then
241                  !! CaCO3:      latitudinally-based fraction of total
242                  !!             primary production
243                  !!               0.10 at equator; 0.02 at pole
244                  fcaco3 = xcaco3a + ((xcaco3b - xcaco3a) *                  &
245                                      ((90.0 - abs(gphit(ji,jj))) / 90.0))
246               elseif (jrratio.eq.1) then
247                  !! CaCO3:      Ridgwell et al. (2007) submodel, version 1
248                  !!             this uses SURFACE omega calcite to regulate
249                  !!             rain ratio
250                  if (f_omcal(ji,jj).ge.1.0) then
251                     fq1 = (f_omcal(ji,jj) - 1.0)**0.81
252                  else
253                     fq1 = 0.
254                  endif
255                  fcaco3 = xridg_r0 * fq1
256               elseif (jrratio.eq.2) then
257                  !! CaCO3:      Ridgwell et al. (2007) submodel, version 2
258                  !!             this uses FULL 3D omega calcite to regulate
259                  !!             rain ratio
260                  if (f3_omcal(ji,jj,jk).ge.1.0) then
261                     fq1 = (f3_omcal(ji,jj,jk) - 1.0)**0.81
262                  else
263                     fq1 = 0.
264                  endif
265                  fcaco3 = xridg_r0 * fq1
266               endif
267# else
268               !! CaCO3:      latitudinally-based fraction of total primary
269               !!              production
270               !!               0.10 at equator; 0.02 at pole
271               fcaco3 = xcaco3a + ((xcaco3b - xcaco3a) *                      &
272                                   ((90.0 - abs(gphit(ji,jj))) / 90.0))
273# endif
274               !! AXY (09/03/09): convert CaCO3 production from function of
275               !! primary production into a function of fast-sinking material;
276               !! technically, this is what Dunne et al. (2007) do anyway; they
277               !! convert total primary production estimated from surface
278               !! chlorophyll to an export flux for which they apply conversion
279               !! factors to estimate the various elemental fractions (Si, Ca)
280               ftempca(ji,jj) = ftempc(ji,jj) * fcaco3
281
282# if defined key_roam
283               !! AXY (12/10/18): while DIC and alkalinity typically occur at
284               !! high concentrations in the ocean relative to the fluxes that
285               !! affect them, there are occasions when fluxes are comparable
286               !! to local concentrations; for example, the "microboils" found
287               !! in UKESM1 produce very temporary (<< 1 day) T & S excursions
288               !! that also affect BGC tracers, moving them towards near-zero
289               !! concentrations; this causes carbonate chemistry deviations
290               !! that, in turn, potentially support CaCO3 production that is
291               !! in excess of local availability of DIC and alkalinity; the
292               !! following code ensures that ftempca does not exceed the local
293               !! capacities of both tracers
294               fq0 = 0.1  ! threshold change limiter
295               fq1 = min(ftempca(ji,jj), (zdic(ji,jj) * fq0))        ! DIC
296               fq2 = min(ftempca(ji,jj) * 2.0, (zalk(ji,jj) * fq0))  ! ALK
297               fq3 = min(fq1, (fq2 / 2.0))  ! select smallest flux
298               ftempca(ji,jj) = fq3  ! reset CaCO3 production
299# endif               
300
301# if defined key_debug_medusa
302               !! integrate total fast detritus production
303               if (idf.eq.1) then
304                  fifd_n(ji,jj)  = fifd_n(ji,jj)  + (ftempn(ji,jj)  *         &
305                                                     fse3t(ji,jj,jk))
306                  fifd_si(ji,jj) = fifd_si(ji,jj) + (ftempsi(ji,jj) *         &
307                                                     fse3t(ji,jj,jk))
308                  fifd_fe(ji,jj) = fifd_fe(ji,jj) + (ftempfe(ji,jj) *         &
309                                                     fse3t(ji,jj,jk))
310#  if defined key_roam
311                  fifd_c(ji,jj)  = fifd_c(ji,jj)  + (ftempc(ji,jj)  *         &
312                                                     fse3t(ji,jj,jk))
313#  endif
314               endif
315
316               !! report quantities of fast-sinking detritus for each component
317               if (idf.eq.1.AND.idfval.eq.1) then
318                  IF (lwp) write (numout,*) '------------------------------'
319! These variables are not in this routine - marc 28/4/17
320!                  IF (lwp) write (numout,*) 'fdpd(',jk,')    = ', fdpd(ji,jj)
321!                  IF (lwp) write (numout,*) 'fdzme(',jk,')   = ', fdzme(ji,jj)
322                  IF (lwp) write (numout,*) 'ftempn(',jk,')  = ', ftempn(ji,jj)
323                  IF (lwp) write (numout,*) 'ftempsi(',jk,') = ', ftempsi(ji,jj)
324                  IF (lwp) write (numout,*) 'ftempfe(',jk,') = ', ftempfe(ji,jj)
325                  IF (lwp) write (numout,*) 'ftempc(',jk,')  = ', ftempc(ji,jj)
326                  IF (lwp) write (numout,*) 'ftempca(',jk,') = ', ftempca(ji,jj)
327                  IF (lwp) write (numout,*) 'flat(',jk,')    = ',             &
328                                            abs(gphit(ji,jj))
329                  IF (lwp) write (numout,*) 'fcaco3(',jk,')  = ', fcaco3
330               endif
331# endif
332            ENDIF
333         ENDDO
334      ENDDO
335
336      !!----------------------------------------------------------
337      !! This version of MEDUSA offers a choice of three methods for
338      !! handling the remineralisation of fast detritus.  All three
339      !! do so in broadly the same way:
340      !!
341      !!   1.  Fast detritus is stored as a 2D array  [ ffastX  ]
342      !!   2.  Fast detritus is added level-by-level  [ ftempX  ]
343      !!   3.  Fast detritus is not remineralised in the top box
344      !!       [ freminX ]
345      !!   4.  Remaining fast detritus is remineralised in the
346      !!       bottom  [ fsedX   ] box
347      !!
348      !! The three remineralisation methods are:
349      !!   
350      !!   1.  Ballast model (i.e. that published in Yool et al.,
351      !!       2011)
352      !!  (1b. Ballast-sans-ballast model)
353      !!   2.  Martin et al. (1987)
354      !!   3.  Henson et al. (2011)
355      !!
356      !! The first of these couples C, N and Fe remineralisation to
357      !! the remineralisation of particulate Si and CaCO3, but the
358      !! latter two treat remineralisation of C, N, Fe, Si and CaCO3
359      !! completely separately.  At present a switch within the code
360      !! regulates which submodel is used, but this should be moved
361      !! to the namelist file.
362      !!
363      !! The ballast-sans-ballast submodel is an original development
364      !! feature of MEDUSA in which the ballast submodel's general
365      !! framework and parameterisation is used, but in which there
366      !! is no protection of organic material afforded by ballasting
367      !! minerals.  While similar, it is not the same as the Martin
368      !! et al. (1987) submodel.
369      !!
370      !! Since the three submodels behave the same in terms of
371      !! accumulating sinking material and remineralising it all at
372      !! the seafloor, these portions of the code below are common to
373      !! all three.
374      !!----------------------------------------------------------
375      if (jexport.eq.1) then
376         DO jj = 2,jpjm1
377            DO ji = 2,jpim1
378               if (tmask(ji,jj,jk) == 1) then
379                  !!=======================================================
380                  !! BALLAST SUBMODEL
381                  !!=======================================================
382                  !!
383                  !!-------------------------------------------------------
384                  !! Fast-sinking detritus fluxes, pt. 1: REMINERALISATION
385                  !! aside from explicitly modelled, slow-sinking detritus, the
386                  !! model includes an implicit representation of detrital
387                  !! particles that sink too quickly to be modelled with
388                  !! explicit state variables; this sinking flux is instead
389                  !! instantaneously remineralised down the water column using
390                  !! the version of Armstrong et al. (2002)'s ballast model
391                  !! used by Dunne et al. (2007); the version of this model
392                  !! here considers silicon and calcium carbonate ballast
393                  !! minerals; this section of the code redistributes the fast
394                  !! sinking material generated locally down the water column;
395                  !! this differs from Dunne et al. (2007) in that fast sinking
396                  !! material is distributed at *every* level below that it is
397                  !! generated, rather than at every level below some fixed
398                  !! depth; this scheme is also different in that sinking
399                  !! material generated in one level is aggregated with that
400                  !! generated by shallower levels; this should make the
401                  !! ballast model more self-consistent (famous last words)
402                  !!-------------------------------------------------------
403                  !!
404                  if (jk.eq.1) then
405                     !! this is the SURFACE OCEAN BOX (no remineralisation)
406                     !!
407                     freminc(ji,jj)  = 0.0
408                     freminn(ji,jj)  = 0.0
409                     freminfe(ji,jj) = 0.0
410                     freminsi(ji,jj) = 0.0
411                     freminca(ji,jj) = 0.0
412                  elseif (jk.le.mbathy(ji,jj)) then
413                     !! this is an OCEAN BOX (remineralise some material)
414                     !!
415                     !! set up CCD depth to be used depending on user choice
416                     if (jocalccd.eq.0) then
417                        !! use default CCD field
418                        fccd_dep(ji,jj) = ocal_ccd(ji,jj)
419                     elseif (jocalccd.eq.1) then
420                        !! use calculated CCD field
421                        fccd_dep(ji,jj) = f2_ccd_cal(ji,jj)
422                     endif
423                     !!
424                     !! === organic carbon ===
425                     !! how much organic C enters this box        (mol)
426                     fq0      = ffastc(ji,jj)
427                     if (iball.eq.1) then
428                        !! how much it weighs
429                        fq1      = (fq0 * xmassc)
430                        !! how much CaCO3 enters this box
431                        fq2      = (ffastca(ji,jj) * xmassca)
432                        !! how much  opal enters this box
433                        fq3      = (ffastsi(ji,jj) * xmasssi)
434                        !! total protected organic C
435                        fq4      = (fq2 * xprotca) + (fq3 * xprotsi)
436                        !! This next term is calculated for C but used for
437                        !! N and Fe as well
438                        !! It needs to be protected in case ALL C is protected
439                        if (fq4.lt.fq1) then
440                           !! protected fraction of total organic C (non-dim)
441                           fprotf   = (fq4 / (fq1 + tiny(fq1)))
442                        else
443                           !! all organic C is protected (non-dim)
444                           fprotf   = 1.0
445                        endif
446                        !! unprotected fraction of total organic C (non-dim)
447                        fq5      = (1.0 - fprotf)
448                        !! how much organic C is unprotected (mol)
449                        fq6      = (fq0 * fq5)
450                        !! how much unprotected C leaves this box (mol)
451                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))
452                        !! how much total C leaves this box (mol)
453                        fq8      = (fq7 + (fq0 * fprotf))
454                        !! C remineralisation in this box (mol)
455                        freminc(ji,jj)  = (fq0 - fq8) / fse3t(ji,jj,jk)
456                        ffastc(ji,jj) = fq8
457# if defined key_debug_medusa
458                        !! report in/out/remin fluxes of carbon for this level
459                           if (idf.eq.1.AND.idfval.eq.1) then
460                              IF (lwp) write (numout,*)                       &
461                                       '------------------------------'
462                              IF (lwp) write (numout,*) 'totalC(',jk,')  = ', &
463                                       fq1
464                              IF (lwp) write (numout,*) 'prtctC(',jk,')  = ', &
465                                       fq4
466                              IF (lwp) write (numout,*) 'fprotf(',jk,')  = ', &
467                                       fprotf
468                              IF (lwp) write (numout,*)                       &
469                                       '------------------------------'
470                              IF (lwp) write (numout,*) 'IN   C(',jk,')  = ', &
471                                       fq0
472                              IF (lwp) write (numout,*) 'LOST C(',jk,')  = ', &
473                                       freminc(ji,jj) * fse3t(ji,jj,jk)
474                              IF (lwp) write (numout,*) 'OUT  C(',jk,')  = ', &
475                                       fq8
476                              IF (lwp) write (numout,*) 'NEW  C(',jk,')  = ', &
477                                       ftempc(ji,jj) * fse3t(ji,jj,jk)
478                           endif
479# endif
480                        else
481                        !! how much organic C leaves this box (mol)
482                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))
483                        !! C remineralisation in this box (mol)
484                        freminc(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)
485                        ffastc(ji,jj)  = fq1
486                     endif
487                     !!
488                     !! === organic nitrogen ===
489                     !! how much organic N enters this box (mol)
490                     fq0      = ffastn(ji,jj)
491                     if (iball.eq.1) then
492                        !! unprotected fraction of total organic N (non-dim)
493                        fq5      = (1.0 - fprotf)
494                        !! how much organic N is unprotected (mol)
495                        fq6      = (fq0 * fq5)
496                        !! how much unprotected N leaves this box (mol)
497                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))
498                        !! how much total N leaves this box (mol)
499                        fq8      = (fq7 + (fq0 * fprotf))
500                        !! N remineralisation in this box (mol)
501                        freminn(ji,jj)  = (fq0 - fq8) / fse3t(ji,jj,jk)
502                        ffastn(ji,jj)  = fq8
503# if defined key_debug_medusa
504                        !! report in/out/remin fluxes of carbon for this level
505                        if (idf.eq.1.AND.idfval.eq.1) then
506                           IF (lwp) write (numout,*)                          &
507                                    '------------------------------'
508                           IF (lwp) write (numout,*) 'totalN(',jk,')  = ', fq1
509                           IF (lwp) write (numout,*) 'prtctN(',jk,')  = ', fq4
510                           IF (lwp) write (numout,*) 'fprotf(',jk,')  = ',    &
511                                    fprotf
512                           IF (lwp) write (numout,*)                          &
513                                    '------------------------------'
514                           if (freminn(ji,jj) < 0.0) then
515                              IF (lwp) write (numout,*) '** FREMIN ERROR **'
516                           endif
517                           IF (lwp) write (numout,*) 'IN   N(',jk,')  = ', fq0
518                           IF (lwp) write (numout,*) 'LOST N(',jk,')  = ',    &
519                                    freminn(ji,jj) * fse3t(ji,jj,jk)
520                           IF (lwp) write (numout,*) 'OUT  N(',jk,')  = ', fq8
521                           IF (lwp) write (numout,*) 'NEW  N(',jk,')  = ',    &
522                                    ftempn(ji,jj) * fse3t(ji,jj,jk)
523                        endif
524# endif
525                     else
526                        !! how much organic N leaves this box (mol)
527                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))
528                        !! N remineralisation in this box (mol)
529                        freminn(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)
530                        ffastn(ji,jj)  = fq1
531                     endif
532                     !!
533                     !! === organic iron ===
534                     !! how much organic Fe enters this box (mol)
535                     fq0      = ffastfe(ji,jj)
536                     if (iball.eq.1) then
537                        !! unprotected fraction of total organic Fe (non-dim)
538                        fq5      = (1.0 - fprotf)
539                        !! how much organic Fe is unprotected (mol)
540                        fq6      = (fq0 * fq5)
541                        !! how much unprotected Fe leaves this box (mol)
542                        fq7      = (fq6 * exp(-(fse3t(ji,jj,jk) / xfastc)))
543                        !! how much total Fe leaves this box (mol)
544                        fq8      = (fq7 + (fq0 * fprotf))
545                        !! Fe remineralisation in this box (mol)
546                        freminfe(ji,jj) = (fq0 - fq8) / fse3t(ji,jj,jk)
547                        ffastfe(ji,jj) = fq8
548                     else
549                        !! how much total Fe leaves this box (mol)
550                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastc))
551                        !! Fe remineralisation in this box (mol)
552                        freminfe(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
553                        ffastfe(ji,jj) = fq1
554                     endif
555                     !!
556                     !! === biogenic silicon ===
557                     !! how much  opal centers this box (mol)
558                     fq0      = ffastsi(ji,jj)
559                     !! how much  opal leaves this box (mol)
560                     fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastsi))
561                     !! Si remineralisation in this box (mol)
562                     freminsi(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
563                     ffastsi(ji,jj) = fq1
564                     !!
565                     !! === biogenic calcium carbonate ===
566                     !! how much CaCO3 enters this box (mol)
567                     fq0      = ffastca(ji,jj)
568                     if (fsdepw(ji,jj,jk).le.fccd_dep(ji,jj)) then
569                        !! whole grid cell above CCD
570                        !! above lysocline, no Ca dissolves (mol)
571                        fq1      = fq0
572                        !! above lysocline, no Ca dissolves (mol)
573                        freminca(ji,jj) = 0.0
574                        !! which is the last level above the CCD?    (#)
575                        fccd(ji,jj) = real(jk)
576                     elseif (fsdepw(ji,jj,jk).ge.fccd_dep(ji,jj)) then
577                        !! whole grid cell below CCD
578                        !! how much CaCO3 leaves this box (mol)
579                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastca))
580                        !! Ca remineralisation in this box (mol)
581                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
582                     else
583                        !! partial grid cell below CCD
584                        !! amount of grid cell below CCD (m)
585                        fq2      = fdep1(ji,jj) - fccd_dep(ji,jj)
586                        !! how much CaCO3 leaves this box (mol)
587                        fq1      = fq0 * exp(-(fq2 / xfastca))
588                        !! Ca remineralisation in this box (mol)
589                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
590                     endif
591                     ffastca(ji,jj) = fq1 
592                  else
593                     !! this is BELOW THE LAST OCEAN BOX (do nothing)
594                     freminc(ji,jj)  = 0.0
595                     freminn(ji,jj)  = 0.0
596                     freminfe(ji,jj) = 0.0
597                     freminsi(ji,jj) = 0.0
598                     freminca(ji,jj) = 0.0             
599                  endif
600               ENDIF
601            ENDDO
602         ENDDO
603      elseif (jexport.eq.2.or.jexport.eq.3) then
604         DO jj = 2,jpjm1
605            DO ji = 2,jpim1
606               if (tmask(ji,jj,jk) == 1) then
607                  if (jexport.eq.2) then
608                     !!====================================================
609                     !! MARTIN ET AL. (1987) SUBMODEL
610                     !!====================================================
611                     !!
612                     !!----------------------------------------------------
613                     !! This submodel uses the classic Martin et al. (1987)
614                     !! curve to determine the attenuation of fast-sinking
615                     !! detritus down the water column.  All three organic
616                     !! elements, C, N and Fe, are handled identically, and
617                     !! their quantities in sinking particles attenuate
618                     !! according to a power relationship governed by
619                     !! parameter "b".  This is assigned a canonical value
620                     !! of -0.858.  Biogenic opal and calcium carbonate are
621                     !! attentuated using the same function as in the
622                     !! ballast submodel
623                     !!----------------------------------------------------
624                     !!
625                     fb_val = -0.858
626                  elseif (jexport.eq.3) then
627                     !!====================================================
628                     !! HENSON ET AL. (2011) SUBMODEL
629                     !!====================================================
630                     !!
631                     !!----------------------------------------------------
632                     !! This submodel reconfigures the Martin et al. (1987)
633                     !! curve by allowing the "b" value to vary
634                     !! geographically.  Its value is set, following Henson
635                     !! et al. (2011), as a function of local sea surface
636                     !! temperature:
637                     !!   b = -1.06 + (0.024 * SST)
638                     !! This means that remineralisation length scales are
639                     !! longer in warm, tropical areas and shorter in cold,
640                     !! polar areas.  This does seem back-to-front (i.e.
641                     !! one would expect GREATER remineralisation in warmer
642                     !! waters), but is an outcome of analysis of sediment
643                     !! trap data, and it may reflect details of ecosystem
644                     !! structure that pertain to particle production
645                     !! rather than simply Q10.
646                     !!----------------------------------------------------
647                     !!
648                     fl_sst = tsn(ji,jj,1,jp_tem)
649                     fb_val = -1.06 + (0.024 * fl_sst)
650                  endif
651                  !!   
652                  if (jk.eq.1) then
653                     !! this is the SURFACE OCEAN BOX (no remineralisation)
654                     !!
655                     freminc(ji,jj)  = 0.0
656                     freminn(ji,jj)  = 0.0
657                     freminfe(ji,jj) = 0.0
658                     freminsi(ji,jj) = 0.0
659                     freminca(ji,jj) = 0.0
660                  elseif (jk.le.mbathy(ji,jj)) then
661                     !! this is an OCEAN BOX (remineralise some material)
662                     !!
663                     !! === organic carbon ===
664                     !! how much organic C enters this box (mol)
665                     fq0      = ffastc(ji,jj)
666                     !! how much organic C leaves this box (mol)
667                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)
668                     !! C remineralisation in this box (mol)
669                     freminc(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)
670                     ffastc(ji,jj)  = fq1
671                     !!
672                     !! === organic nitrogen ===
673                     !! how much organic N enters this box (mol)
674                     fq0      = ffastn(ji,jj)
675                     !! how much organic N leaves this box (mol)
676                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)
677                     !! N remineralisation in this box (mol)
678                     freminn(ji,jj)  = (fq0 - fq1) / fse3t(ji,jj,jk)
679                     ffastn(ji,jj)  = fq1
680                     !!
681                     !! === organic iron ===
682                     !! how much organic Fe enters this box (mol)
683                     fq0      = ffastfe(ji,jj)
684                     !! how much organic Fe leaves this box (mol)
685                     fq1      = fq0 * ((fdep1(ji,jj)/fsdepw(ji,jj,jk))**fb_val)
686                     !! Fe remineralisation in this box (mol)
687                     freminfe(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
688                     ffastfe(ji,jj) = fq1
689                     !!
690                     !! === biogenic silicon ===
691                     !! how much  opal centers this box (mol)
692                     fq0      = ffastsi(ji,jj)
693                     !! how much  opal leaves this box (mol)
694                     fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastsi))
695                     !! Si remineralisation in this box (mol)
696                     freminsi(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
697                     ffastsi(ji,jj) = fq1
698                     !!
699                     !! === biogenic calcium carbonate ===
700                     !! how much CaCO3 enters this box (mol)
701                     fq0      = ffastca(ji,jj)
702                     if (fsdepw(ji,jj,jk).le.ocal_ccd(ji,jj)) then
703                        !! whole grid cell above CCD
704                        !! above lysocline, no Ca dissolves (mol)
705                        fq1      = fq0
706                        !! above lysocline, no Ca dissolves (mol)
707                        freminca(ji,jj) = 0.0
708                        !! which is the last level above the CCD?    (#)
709                        fccd(ji,jj) = real(jk)
710                     elseif (fsdepw(ji,jj,jk).ge.ocal_ccd(ji,jj)) then
711                        !! whole grid cell below CCD
712                        !! how much CaCO3 leaves this box (mol)
713                        fq1      = fq0 * exp(-(fse3t(ji,jj,jk) / xfastca))
714                        !! Ca remineralisation in this box (mol)
715                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
716                     else
717                        !! partial grid cell below CCD
718                        !! amount of grid cell below CCD (m)
719                        fq2      = fdep1(ji,jj) - ocal_ccd(ji,jj)
720                        !! how much CaCO3 leaves this box (mol)
721                        fq1      = fq0 * exp(-(fq2 / xfastca))
722                        !! Ca remineralisation in this box (mol)
723                        freminca(ji,jj) = (fq0 - fq1) / fse3t(ji,jj,jk)
724                     endif
725                     ffastca(ji,jj) = fq1 
726                  else
727                     !! this is BELOW THE LAST OCEAN BOX (do nothing)
728                     freminc(ji,jj)  = 0.0
729                     freminn(ji,jj)  = 0.0
730                     freminfe(ji,jj) = 0.0
731                     freminsi(ji,jj) = 0.0
732                     freminca(ji,jj) = 0.0             
733                  endif
734               ENDIF
735            ENDDO
736         ENDDO
737      endif
738
739      DO jj = 2,jpjm1
740         DO ji = 2,jpim1
741            if (tmask(ji,jj,jk) == 1) then
742               !!----------------------------------------------------------
743               !! Fast-sinking detritus fluxes, pt. 2: UPDATE FAST FLUXES
744               !! here locally calculated additions to the fast-sinking
745               !! flux are added to the total fast-sinking flux; this is
746               !! done here such that material produced in a particular
747               !! layer is only remineralised below this layer
748               !!----------------------------------------------------------
749               !!
750               !! add sinking material generated in this layer to running
751               !! totals
752               !!
753               !! === organic carbon ===
754               !! (diatom and mesozooplankton mortality)
755               ffastc(ji,jj)  = ffastc(ji,jj)  + (ftempc(ji,jj)  *           &
756                                                  fse3t(ji,jj,jk))
757               !!
758               !! === organic nitrogen ===
759               !! (diatom and mesozooplankton mortality)
760               ffastn(ji,jj)  = ffastn(ji,jj)  + (ftempn(ji,jj)  *           &
761                                                  fse3t(ji,jj,jk))
762               !!
763               !! === organic iron ===
764               !! (diatom and mesozooplankton mortality)
765               ffastfe(ji,jj) = ffastfe(ji,jj) + (ftempfe(ji,jj) *          &
766                                                  fse3t(ji,jj,jk))
767               !!
768               !! === biogenic silicon ===
769               !! (diatom mortality and grazed diatoms)
770               ffastsi(ji,jj) = ffastsi(ji,jj) + (ftempsi(ji,jj) *          &
771                                                  fse3t(ji,jj,jk))
772               !!
773               !! === biogenic calcium carbonate ===
774               !! (latitudinally-based fraction of total primary production)
775               ffastca(ji,jj) = ffastca(ji,jj) + (ftempca(ji,jj) *          &
776                                                  fse3t(ji,jj,jk))
777            ENDIF
778         ENDDO
779      ENDDO
780
781      DO jj = 2,jpjm1
782         DO ji = 2,jpim1
783            if (tmask(ji,jj,jk) == 1) then
784               !!----------------------------------------------------------
785               !! Fast-sinking detritus fluxes, pt. 3: SEAFLOOR
786               !! remineralise all remaining fast-sinking detritus to dissolved
787               !! nutrients; the sedimentation fluxes calculated here allow the
788               !! separation of what's remineralised sinking through the final
789               !! ocean box from that which is added to the final box by the
790               !! remineralisation of material that reaches the seafloor (i.e.
791               !! the model assumes that *all* material that hits the seafloor
792               !! is remineralised and that none is permanently buried; hey,
793               !! this is a giant GCM model that can't be run for long enough
794               !! to deal with burial fluxes!)
795               !!
796               !! in a change to this process, in part so that MEDUSA behaves
797               !! a little more like ERSEM et al., fast-sinking detritus (N, Fe
798               !! and C) is converted to slow sinking detritus at the seafloor
799               !! instead of being remineralised; the rationale is that in
800               !! shallower shelf regions (... that are not fully mixed!) this
801               !! allows the detrital material to return slowly to dissolved
802               !! nutrient rather than instantaneously as now; the alternative
803               !! would be to explicitly handle seafloor organic material - a
804               !! headache I don't wish to experience at this point; note that
805               !! fast-sinking Si and Ca detritus is just remineralised as
806               !! per usual
807               !!
808               !! AXY (13/01/12)
809               !! in a further change to this process, again so that MEDUSA is
810               !! a little more like ERSEM et al., material that reaches the
811               !! seafloor can now be added to sediment pools and stored for
812               !! slow release; there are new 2D arrays for organic nitrogen,
813               !! iron and carbon and inorganic silicon and carbon that allow
814               !! fast and slow detritus that reaches the seafloor to be held
815               !! and released back to the water column more slowly; these
816               !! arrays are transferred via the tracer restart files between
817               !! repeat submissions of the model
818               !!----------------------------------------------------------
819               !!
820               ffast2slowc(ji,jj)  = 0.0
821               ffast2slown(ji,jj)  = 0.0
822! I don't think this is used - marc 10/4/17
823!               ffast2slowfe(ji,jj) = 0.0
824               !!
825               if (jk.eq.mbathy(ji,jj)) then
826                  !! this is the BOTTOM OCEAN BOX (remineralise everything)
827                  !!
828                  !! AXY (17/01/12): tweaked to include benthos pools
829                  !!
830                  !! === organic carbon ===
831                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
832                     !! C remineralisation in this box (mol/m3)
833                     freminc(ji,jj)  = freminc(ji,jj) + (ffastc(ji,jj) /     &
834                                                         fse3t(ji,jj,jk))
835                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
836                     !! fast C -> slow C (mol/m3)
837                     ffast2slowc(ji,jj) = ffastc(ji,jj) / fse3t(ji,jj,jk)
838                     fslowc(ji,jj)      = fslowc(ji,jj) + ffast2slowc(ji,jj)
839                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
840                     !! fast C -> benthic C (mol/m2)
841                     f_fbenin_c(ji,jj)  = ffastc(ji,jj)
842                  endif
843                  !! record seafloor C (mol/m2)
844                  fsedc(ji,jj)   = ffastc(ji,jj)
845                  ffastc(ji,jj)  = 0.0
846                  !!
847                  !! === organic nitrogen ===
848                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
849                     !! N remineralisation in this box (mol/m3)
850                     freminn(ji,jj)  = freminn(ji,jj) + (ffastn(ji,jj) /     &
851                                                         fse3t(ji,jj,jk))
852                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
853                     !! fast N -> slow N (mol/m3)
854                     ffast2slown(ji,jj) = ffastn(ji,jj) / fse3t(ji,jj,jk)
855                     fslown(ji,jj)      = fslown(ji,jj) + ffast2slown(ji,jj)
856                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
857                     !! fast N -> benthic N (mol/m2)
858                     f_fbenin_n(ji,jj)  = ffastn(ji,jj)
859                  endif
860                  !! record seafloor N (mol/m2)
861                  fsedn(ji,jj)   = ffastn(ji,jj)
862                  ffastn(ji,jj)  = 0.0
863                  !!
864                  !! === organic iron ===
865                  if (jfdfate.eq.0 .and. jorgben.eq.0) then
866                     !! Fe remineralisation in this box (mol/m3)
867                     freminfe(ji,jj) = freminfe(ji,jj) + (ffastfe(ji,jj) /   &
868                                                          fse3t(ji,jj,jk))
869! I don't think ffast2slowfe is used - marc 10/4/17
870!                  elseif (jfdfate.eq.1 .and. jorgben.eq.0) then
871!                     !! fast Fe -> slow Fe (mol/m3)
872!                     ffast2slowfe(ji,jj) = ffastn(ji,jj) / fse3t(ji,jj,jk)
873                  elseif (jfdfate.eq.0 .and. jorgben.eq.1) then
874                     !! fast Fe -> benthic Fe (mol/m2)
875                     f_fbenin_fe(ji,jj) = ffastfe(ji,jj)
876                  endif
877                  !! record seafloor Fe (mol/m2)
878                  fsedfe(ji,jj)  = ffastfe(ji,jj)
879                  ffastfe(ji,jj) = 0.0
880                  !!
881                  !! === biogenic silicon ===
882                  if (jinorgben.eq.0) then
883                     !! Si remineralisation in this box (mol/m3)
884                     freminsi(ji,jj) = freminsi(ji,jj) + (ffastsi(ji,jj) /   &
885                                                          fse3t(ji,jj,jk))
886                  elseif (jinorgben.eq.1) then
887                     !! fast Si -> benthic Si
888                     f_fbenin_si(ji,jj) = ffastsi(ji,jj)
889                  endif
890                  !! record seafloor Si (mol/m2)
891                  fsedsi(ji,jj)   = ffastsi(ji,jj)
892                  ffastsi(ji,jj) = 0.0
893                  !!
894                  !! === biogenic calcium carbonate ===
895                  if (jinorgben.eq.0) then
896                     !! Ca remineralisation in this box (mol/m3)
897                     freminca(ji,jj) = freminca(ji,jj) + (ffastca(ji,jj) /   &
898                                                          fse3t(ji,jj,jk))
899                  elseif (jinorgben.eq.1) then
900                     !! fast Ca -> benthic Ca (mol/m2)
901                     f_fbenin_ca(ji,jj) = ffastca(ji,jj)
902                  endif
903                  !! record seafloor Ca (mol/m2)
904                  fsedca(ji,jj)   = ffastca(ji,jj)
905                  ffastca(ji,jj) = 0.0
906               endif
907
908# if defined key_debug_medusa
909               if (idf.eq.1) then
910                  !!-------------------------------------------------------
911                  !! Integrate total fast detritus remineralisation
912                  !!-------------------------------------------------------
913                  !!
914                  fofd_n(ji,jj)  = fofd_n(ji,jj)  + (freminn(ji,jj)  *       &
915                                                     fse3t(ji,jj,jk))
916                  fofd_si(ji,jj) = fofd_si(ji,jj) + (freminsi(ji,jj) *       &
917                                                     fse3t(ji,jj,jk))
918                  fofd_fe(ji,jj) = fofd_fe(ji,jj) + (freminfe(ji,jj) *       &
919                                                     fse3t(ji,jj,jk))
920#  if defined key_roam
921                  fofd_c(ji,jj)  = fofd_c(ji,jj)  + (freminc(ji,jj)  *       &
922                                                     fse3t(ji,jj,jk))
923#  endif
924               endif
925# endif
926            ENDIF
927         ENDDO
928      ENDDO
929
930      DO jj = 2,jpjm1
931         DO ji = 2,jpim1
932            if (tmask(ji,jj,jk) == 1) then
933               !!----------------------------------------------------------
934               !! Sort out remineralisation tally of fast-sinking detritus
935               !!----------------------------------------------------------
936               !!
937               !! update fast-sinking regeneration arrays
938               fregenfast(ji,jj)   = fregenfast(ji,jj)   +                  &
939                                     (freminn(ji,jj)  * fse3t(ji,jj,jk))
940               fregenfastsi(ji,jj) = fregenfastsi(ji,jj) +                  &
941                                     (freminsi(ji,jj) * fse3t(ji,jj,jk))
942# if defined key_roam
943               fregenfastc(ji,jj)  = fregenfastc(ji,jj)  +                  &
944                                     (freminc(ji,jj)  * fse3t(ji,jj,jk))
945# endif
946            ENDIF
947         ENDDO
948      ENDDO
949
950      DO jj = 2,jpjm1
951         DO ji = 2,jpim1
952            if (tmask(ji,jj,jk) == 1) then
953               !!----------------------------------------------------------
954               !! Benthic remineralisation fluxes
955               !!----------------------------------------------------------
956               !!
957               if (jk.eq.mbathy(ji,jj)) then
958                  !!
959                  !! organic components
960                  if (jorgben.eq.1) then
961                     f_benout_n(ji,jj)  = xsedn  * zn_sed_n(ji,jj)
962                     f_benout_fe(ji,jj) = xsedfe * zn_sed_fe(ji,jj)
963                     f_benout_c(ji,jj)  = xsedc  * zn_sed_c(ji,jj)
964                  endif
965                  !!
966                  !! inorganic components
967                  if (jinorgben.eq.1) then
968                     f_benout_si(ji,jj) = xsedsi * zn_sed_si(ji,jj)
969                     f_benout_ca(ji,jj) = xsedca * zn_sed_ca(ji,jj)
970                     !!
971                     !! account for CaCO3 that dissolves when it shouldn't
972                     if ( fsdepw(ji,jj,jk) .le. fccd_dep(ji,jj) ) then
973                        f_benout_lyso_ca(ji,jj) = xsedca * zn_sed_ca(ji,jj)
974                     endif
975                  endif
976               endif
977               CALL flush(numout)
978
979            ENDIF
980         ENDDO
981      ENDDO
982
983   END SUBROUTINE detritus_fast_sink
984
985#else
986   !!======================================================================
987   !!  Dummy module :                                   No MEDUSA bio-model
988   !!======================================================================
989CONTAINS
990   SUBROUTINE detritus_fast_sink( )                    ! Empty routine
991      WRITE(*,*) 'detritus_fast_sink: You should not have seen this print! error?'
992   END SUBROUTINE detritus_fast_sink
993#endif 
994
995   !!======================================================================
996END MODULE detritus_fast_sink_mod
Note: See TracBrowser for help on using the repository browser.