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

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/MEDUSA/detritus_fast_sink.F90

Last change on this file was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

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