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

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC/MEDUSA/iron_chem_scav.F90 @ 10149

Last change on this file since 10149 was 10020, checked in by marc, 6 years ago

GMED ticket 406. CPP key fixes.

File size: 25.1 KB
Line 
1MODULE iron_chem_scav_mod
2   !!======================================================================
3   !!                         ***  MODULE iron_chem_scav_mod  ***
4   !! Calculate the iron chemistry and scavenging.
5   !!======================================================================
6   !! History :
7   !!   -   ! 2017-04 (M. Stringer)        Code taken from trcbio_medusa.F90
8   !!----------------------------------------------------------------------
9#if defined key_medusa
10   !!----------------------------------------------------------------------
11   !!                                                   MEDUSA bio-model
12   !!----------------------------------------------------------------------
13
14   IMPLICIT NONE
15   PRIVATE
16     
17   PUBLIC   iron_chem_scav        ! Called in trcbio_medusa.F90
18
19   !!----------------------------------------------------------------------
20   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
21   !! $Id$
22   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
23   !!----------------------------------------------------------------------
24
25CONTAINS
26
27   SUBROUTINE iron_chem_scav( jk )
28      !!-------------------------------------------------------------------
29      !!                     ***  ROUTINE iron_chem_scav  ***
30      !! This called from TRC_BIO_MEDUSA and
31      !!  -
32      !!-------------------------------------------------------------------
33      USE bio_medusa_mod,    ONLY: ffastc, ffastca, ffastsi,              &
34                                   ffetop, ffebot, ffescav, xfree,        & 
35                                   zdet, zfer, zphd, zphn, zzme, zzmi,    &
36                                   idf, idfval                         
37      USE dom_oce,           ONLY: e3t_0, gdepw_0, mbathy, tmask
38#if defined key_vvl
39      USE dom_oce,           ONLY: e3t_n, gdepw_n
40#endif
41      USE par_kind,          ONLY: wp
42      USE in_out_manager,    ONLY: lwp, numout
43      USE par_oce,           ONLY: jpi, jpim1, jpj, jpjm1
44      USE sms_medusa,        ONLY: i0500, jiron, xfe_sed, xfe_sol,        &
45                                   xfe_mass,                              &
46                                   xk_FeL, xk_sc_Fe, xLgT,                &
47                                   xmassc, xmassca, xmasssi,              &
48                                   xthetad, xthetapd, xthetapn,           &
49                                   xthetazme, xthetazmi,                  &
50                                   zirondep
51
52   !!* Substitution
53#  include "domzgr_substitute.h90"
54
55      !! Level
56      INTEGER, INTENT( in ) :: jk
57
58      !! iron cycle; includes parameters for Parekh et al. (2005) iron scheme
59      !! state variables for iron-ligand system
60      REAL(wp), DIMENSION(jpi,jpj) :: xFeT, xFeF, xFeL
61      REAL(wp) :: xLgF
62      !! iron-ligand parameters
63      REAL(wp) :: xb_coef_tmp, xb2M4ac
64      !! max Fe' parameters
65      REAL(wp) :: xmaxFeF,fdeltaFe
66      !!
67      !! local parameters for Moore et al. (2004) alternative scavenging
68      !! scheme
69      REAL(wp) :: fbase_scav,fscal_sink,fscal_part,fscal_scav
70      !!
71      !! local parameters for Moore et al. (2008) alternative scavenging
72      !! scheme
73      REAL(wp) :: fscal_csink,fscal_sisink,fscal_casink
74      !!
75      !! local parameters for Galbraith et al. (2010) alternative
76      !! scavenging scheme.
77      !! organic portion of scavenging
78      REAL(wp) :: xCscav1, xCscav2, xk_org, xORGscav
79      !! inorganic portion of scavenging
80      REAL(wp) :: xk_inorg, xINORGscav
81
82      INTEGER :: ji, jj
83
84      !!------------------------------------------------------------------
85      !! Iron chemistry and fractionation
86      !! following the Parekh et al. (2004) scheme adopted by the Met.
87      !! Office, Medusa models total iron but considers "free" and
88      !! ligand-bound forms for the purposes of scavenging (only "free"
89      !! iron can be scavenged
90      !!------------------------------------------------------------------
91      DO jj = 2,jpjm1
92         DO ji = 2,jpim1
93            !! OPEN wet point IF..THEN loop
94            if (tmask(ji,jj,jk) == 1) then
95               !!
96               !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
97               xFeT(ji,jj) = zfer(ji,jj) * 1.e3
98               !!
99               !! calculate fractionation (based on Diat-HadOCC; in turn
100               !! based on Parekh et al., 2004)
101               xb_coef_tmp = xk_FeL * (xLgT - xFeT(ji,jj)) - 1.0
102               xb2M4ac     = max(((xb_coef_tmp * xb_coef_tmp) +              &
103                                  (4.0 * xk_FeL * xLgT)), 0.0)
104               !!
105               !! "free" ligand concentration
106               xLgF        = 0.5 * (xb_coef_tmp + (xb2M4ac**0.5)) / xk_FeL
107               !!
108               !! ligand-bound iron concentration
109               xFeL(ji,jj) = xLgT - xLgF
110               !!
111               !! "free" iron concentration (and convert to mmol Fe / m3)
112               xFeF(ji,jj) = (xFeT(ji,jj) - xFeL(ji,jj)) * 1.e-3
113               xFree(ji,jj)= xFeF(ji,jj) / (zfer(ji,jj) + tiny(zfer(ji,jj)))
114            ENDIF
115         ENDDO
116      ENDDO
117
118
119      !!
120      !! scavenging of iron (multiple schemes); I'm only really
121      !! happy with the first one at the moment - the others
122      !! involve assumptions (sometimes guessed at by me) that
123      !! are potentially questionable
124      !!
125      if (jiron.eq.1) then
126         !!------------------------------------------------------
127         !! Scheme 1: Dutkiewicz et al. (2005)
128         !! This scheme includes a single scavenging term based
129         !! solely on a fixed rate and the availablility of
130         !! "free" iron
131         !!------------------------------------------------------
132         DO jj = 2,jpjm1
133            DO ji = 2,jpim1
134               IF (tmask(ji,jj,jk) == 1) THEN
135                  !! = mmol/m3/d
136                  ffescav(ji,jj)     = xk_sc_Fe * xFeF(ji,jj)
137                  !!
138                  !!------------------------------------------------------
139                  !!
140                  !! Mick's code contains a further (optional) implicit
141                  !! "scavenging" of iron that sets an upper bound on
142                  !! "free" iron concentration, and essentially caps the
143                  !! concentration of total iron as xFeL + "free" iron;
144                  !! since the former is constrained by a fixed total
145                  !! ligand concentration (= 1.0 umol/m3), and the latter
146                  !! isn't allowed above this upper bound, total iron is
147                  !! constrained to a maximum of ...
148                  !!
149                  !!    xFeL(ji,jj) + min(xFeF(ji,jj), 0.3 umol/m3) = 1.0 + 0.3
150                  !!                                  = 1.3 umol / m3
151                  !!
152                  !! In Mick's code, the actual value of total iron is
153                  !! reset to this sum (i.e. TFe = FeL + Fe'; but
154                  !! Fe' <= 0.3 umol/m3); this isn't our favoured approach
155                  !! to tracer updating here (not least because of the
156                  !! leapfrog), so here the amount scavenged is augmented
157                  !! by an additional amount that serves to drag total
158                  !! iron back towards that expected from this limitation
159                  !! on iron concentration ...
160                  !!
161                  !! = umol/m3
162                  xmaxFeF     = min((xFeF(ji,jj) * 1.e3), 0.3)
163                  !!
164                  !! Here, the difference between current total Fe and
165                  !! (FeL + Fe') is calculated and added to the scavenging
166                  !! flux already calculated above ...
167                  !!
168                  !! = mmol/m3
169                  fdeltaFe    = (xFeT(ji,jj) - (xFeL(ji,jj) + xmaxFeF)) * 1.e-3
170                  !!
171                  !! This assumes that the "excess" iron is dissipated
172                  !! with a time-scale of 1 day; seems reasonable to me
173                  !! ... (famous last words)
174                  !!
175                  !! = mmol/m3/d
176                  ffescav(ji,jj)     = ffescav(ji,jj) + fdeltaFe
177                  !!
178# if defined key_deep_fe_fix
179                  !! AXY (17/01/13)
180                  !! stop scavenging for iron concentrations below
181                  !! 0.5 umol / m3 at depths greater than 1000 m; this
182                  !! aims to end MEDUSA's continual loss of iron at depth
183                  !! without impacting things at the surface too much; the
184                  !! justification for this is that it appears to be what
185                  !! Mick Follows et al. do in their work (as evidenced by
186                  !! the iron initial condition they supplied me with); to
187                  !! be honest, it looks like Follow et al. do this at
188                  !! shallower depths than 1000 m, but I'll stick with this
189                  !! for now; I suspect that this seemingly arbitrary
190                  !! approach effectively "parameterises" the
191                  !! particle-based scavenging rates that other models use
192                  !! (i.e. at depth there are no sinking particles, so
193                  !! scavenging stops); it might be fun justifying this in
194                  !! a paper though!
195                  !!
196                  if ((fsdepw(ji,jj,jk).gt.1000.) .and.                       &
197                       (xFeT(ji,jj).lt.0.5)) then
198                     ffescav(ji,jj) = 0.
199                  endif
200# endif
201               ENDIF
202            ENDDO
203         ENDDO
204      elseif (jiron.eq.2) then
205         !!------------------------------------------------------
206         !! Scheme 2: Moore et al. (2004)
207         !! This scheme includes a single scavenging term that
208         !! accounts for both suspended and sinking particles in
209         !! the water column; this term scavenges total iron rather
210         !! than "free" iron
211         !!------------------------------------------------------
212         DO jj = 2,jpjm1
213            DO ji = 2,jpim1
214               IF (tmask(ji,jj,jk) == 1) THEN
215                  !!
216                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
217                  xFeT(ji,jj) = zfer(ji,jj) * 1.e3
218                  !!
219                  !! this has a base scavenging rate (12% / y) which is
220                  !! modified by local particle concentration and sinking
221                  !! flux (and dust - but I'm ignoring that here for now)
222                  !! and which is accelerated when Fe concentration gets
223                  !! 0.6 nM (= 0.6 umol/m3 = 0.0006 mmol/m3), and decreased
224                  !! as concentrations below 0.4 nM (= 0.4 umol/m3 =
225                  !! 0.0004 mmol/m3)
226                  !!
227                  !! base scavenging rate (0.12 / y)
228                  fbase_scav = 0.12 / 365.25
229                  !!
230                  !! calculate sinking particle part of scaling factor
231                  !! this takes local fast sinking carbon (mmol C / m2 / d)
232                  !! and gets it into nmol C / cm3 / s ("rdt" below is the
233                  !! number of seconds in a model timestep)
234                  !!
235                  !! fscal_sink = ffastc(ji,jj) * 1.e2 / (86400.)
236                  !!
237                  !! ... actually, re-reading Moore et al.'s equations, it
238                  !! looks like he uses his sinking flux directly, without
239                  !! scaling it by time-step or anything, so I'll copy this
240                  !! here ...
241                  !!
242                  fscal_sink = ffastc(ji,jj) * 1.e2
243                  !!
244                  !! calculate particle part of scaling factor
245                  !! this totals up the carbon in suspended particles
246                  !! (Pn, Pd, Zmi, Zme, D),
247                  !! which comes out in mmol C / m3 (= nmol C / cm3), and
248                  !! then multiplies it by a magic factor, 0.002, to get it
249                  !! into nmol C / cm2 / s
250                  !!
251                  fscal_part = ( (xthetapn * zphn(ji,jj)) +                  &
252                                 (xthetapd * zphd(ji,jj)) +                  &
253                                 (xthetazmi * zzmi(ji,jj)) +                 &
254                                 (xthetazme * zzme(ji,jj)) +                 &
255                                 (xthetad * zdet(ji,jj)) ) * 0.002
256                  !!
257                  !! calculate scaling factor for base scavenging rate
258                  !! this uses the (now correctly scaled) sinking flux and
259                  !! standing
260                  !! particle concentration, divides through by some sort
261                  !! of reference value (= 0.0066 nmol C / cm2 / s) and
262                  !! then uses this, or not if its too high, to rescale the
263                  !! base scavenging rate
264                  !!
265                  fscal_scav = fbase_scav *                                  &
266                               min(((fscal_sink + fscal_part) / 0.0066), 4.0)
267                  !!
268                  !! the resulting scavenging rate is then scaled further
269                  !! according to the local iron concentration (i.e.
270                  !! diminished in low iron regions; enhanced in high iron
271                  !! regions; less alone in intermediate iron regions)
272                  !!
273                  if (xFeT(ji,jj).lt.0.4) then
274                     !!
275                     !! low iron region
276                     !!
277                     fscal_scav = fscal_scav * (xFeT(ji,jj) / 0.4)
278                     !!
279                  elseif (xFeT(ji,jj).gt.0.6) then
280                     !!
281                     !! high iron region
282                     !!
283                     fscal_scav = fscal_scav + ((xFeT(ji,jj) / 0.6) *        &
284                                                (6.0 / 1.4))
285                     !!
286                  else
287                     !!
288                     !! intermediate iron region: do nothing
289                     !!
290                  endif
291                  !!
292                  !! apply the calculated scavenging rate ...
293                  !!
294                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj)
295                  !!
296               ENDIF
297            ENDDO
298         ENDDO
299      elseif (jiron.eq.3) then
300         !!------------------------------------------------------
301         !! Scheme 3: Moore et al. (2008)
302         !! This scheme includes a single scavenging term that
303         !! accounts for sinking particles in the water column,
304         !! and includes organic C, biogenic opal, calcium
305         !! carbonate and dust in this (though the latter is
306         !! ignored here until I work out what units the incoming
307         !! "dust" flux is in); this term scavenges total iron
308         !! rather than "free" iron
309         !!------------------------------------------------------
310         DO jj = 2,jpjm1
311            DO ji = 2,jpim1
312               IF (tmask(ji,jj,jk) == 1) THEN
313                  !!
314                  !! total iron concentration (mmol Fe / m3 -> umol Fe / m3)
315                  xFeT(ji,jj) = zfer(ji,jj) * 1.e3
316                  !!
317                  !! this has a base scavenging rate which is modified by
318                  !! local particle sinking flux (including dust - but I'm
319                  !! ignoring that here for now) and which is accelerated
320                  !! when Fe concentration is > 0.6 nM (= 0.6 umol/m3 =
321                  !! 0.0006 mmol/m3), and decreased as concentrations <
322                  !! 0.5 nM (= 0.5 umol/m3 = 0.0005 mmol/m3)
323                  !!
324                  !! base scavenging rate (Fe_b in paper; units may be
325                  !! wrong there)
326                  fbase_scav = 0.00384 ! (ng)^-1 cm
327                  !!
328                  !! calculate sinking particle part of scaling factor;
329                  !! this converts mmol / m2 / d fluxes of organic carbon,
330                  !! silicon and calcium carbonate into ng / cm2 / s
331                  !! fluxes; it is assumed here that the mass conversions
332                  !! simply consider the mass of the main element
333                  !! (C, Si and Ca) and *not* the mass of the molecules
334                  !! that they are part of; Moore et al. (2008) is unclear
335                  !! on the conversion that should be used
336                  !!
337                  !! milli -> nano; mol -> gram; /m2 -> /cm2; /d -> /s
338                  !! ng C  / cm2 / s
339                  fscal_csink  = (ffastc(ji,jj)  * 1.e6 * xmassc  *          &
340                                  1.e-4 / 86400.)
341                  !! ng Si / cm2 / s
342                  fscal_sisink = (ffastsi(ji,jj) * 1.e6 * xmasssi *          &
343                                  1.e-4 / 86400.)
344                  !! ng Ca / cm2 / s
345                  fscal_casink = (ffastca(ji,jj) * 1.e6 * xmassca *          &
346                                  1.e-4 / 86400.)
347                  !!
348                  !! sum up these sinking fluxes and convert to ng / cm
349                  !! by dividing through by a sinking rate of
350                  !! 100 m / d = 1.157 cm / s
351                  !! ng / cm
352                  fscal_sink   = ((fscal_csink * 6.) + fscal_sisink +        &
353                                  fscal_casink) / (100. * 1.e3 / 86400)
354                  !!
355                  !! now calculate the scavenging rate based upon the base
356                  !! rate and this particle flux scaling; according to the
357                  !! published units, the result actually has *no* units,
358                  !! but as it must be expressed per unit time for it to
359                  !! make any sense, I'm assuming a missing "per second"
360                  !! / s
361                  fscal_scav = fbase_scav * fscal_sink
362                  !!
363                  !! the resulting scavenging rate is then scaled further
364                  !! according to the local iron concentration (i.e.
365                  !! diminished in low iron regions; enhanced in high iron
366                  !! regions; less alone in intermediate iron regions)
367                  !!
368                  if (xFeT(ji,jj).lt.0.5) then
369                     !!
370                     !! low iron region (0.5 instead of the 0.4 in Moore
371                     !! et al., 2004)
372                     !!
373                     fscal_scav = fscal_scav * (xFeT(ji,jj) / 0.5)
374                     !!
375                  elseif (xFeT(ji,jj).gt.0.6) then
376                     !!
377                     !! high iron region (functional form different in
378                     !! Moore et al., 2004)
379                     !!
380                     fscal_scav = fscal_scav + ((xFeT(ji,jj) - 0.6) * 0.00904)
381                     !!
382                  else
383                     !!
384                     !! intermediate iron region: do nothing
385                     !!
386                  endif
387                  !!
388                  !! apply the calculated scavenging rate ...
389                  !!
390                  ffescav(ji,jj) = fscal_scav * zfer(ji,jj)
391               ENDIF
392            ENDDO
393         ENDDO
394      elseif (jiron.eq.4) then
395         !!------------------------------------------------------
396         !! Scheme 4: Galbraith et al. (2010)
397         !! This scheme includes two scavenging terms, one for
398         !! organic, particle-based scavenging, and another for
399         !! inorganic scavenging; both terms scavenge "free" iron
400         !! only
401         !!------------------------------------------------------
402         DO jj = 2,jpjm1
403            DO ji = 2,jpim1
404               IF (tmask(ji,jj,jk) == 1) THEN
405                  !!
406                  !! Galbraith et al. (2010) present a more straightforward
407                  !! outline of the scheme in Parekh et al. (2005) ...
408                  !!
409                  !! sinking particulate carbon available for scavenging
410                  !! this assumes a sinking rate of 100 m / d (Moore &
411                  !! Braucher, 2008),
412                  xCscav1    = (ffastc(ji,jj) * xmassc) / 100. ! = mg C / m3
413                  !!
414                  !! scale by Honeyman et al. (1981) exponent coefficient
415                  !! multiply by 1.e-3 to express C flux in g C rather than
416                  !! mg C
417                  xCscav2    = (xCscav1 * 1.e-3)**0.58
418                  !!
419                  !! multiply by Galbraith et al. (2010) scavenging rate
420                  xk_org     = 0.5 ! ((g C m/3)^-1) / d
421                  xORGscav   = xk_org * xCscav2 * xFeF(ji,jj)
422                  !!
423                  !! Galbraith et al. (2010) also include an inorganic bit ...
424                  !!
425                  !! this occurs at a fixed rate, again based on the
426                  !! availability of "free" iron
427                  !!
428                  !! k_inorg = 1000 d**-1 nmol Fe**-0.5 kg**-0.5
429                  !!
430                  !! to implement this here, scale xFeF by 1026 to put in
431                  !! units of umol/m3 which approximately equal nmol/kg
432                  !!
433                  xk_inorg   = 1000. ! ((nmol Fe / kg)^1.5)
434                  xINORGscav = (xk_inorg * (xFeF(ji,jj) * 1026.)**1.5) * 1.e-3
435                  !!
436                  !! sum these two terms together
437                  ffescav(ji,jj) = xORGscav + xINORGscav
438               ENDIF
439            ENDDO
440         ENDDO
441      else
442         !!------------------------------------------------------
443         !! No Scheme: you coward!
444         !! This scheme puts its head in the sand and eskews any
445         !! decision about how iron is removed from the ocean;
446         !! prepare to get deluged in iron you fool!
447         !!------------------------------------------------------
448         DO jj = 2,jpjm1
449            DO ji = 2,jpim1
450               IF (tmask(ji,jj,jk) == 1) THEN
451                  ffescav(ji,jj) = 0.
452               ENDIF
453            ENDDO
454         ENDDO
455      endif
456
457      !!---------------------------------------------------------
458      !! Other iron cycle processes
459      !!---------------------------------------------------------
460      !!
461      !! aeolian iron deposition
462      !! zirondep      is in mmol-Fe / m2 / day
463      !! ffetop(ji,jj) is in mmol-dissolved-Fe / m3 / day
464      if (jk == 1) then
465         DO jj = 2,jpjm1
466            DO ji = 2,jpim1
467               IF (tmask(ji,jj,jk) == 1) THEN
468                  ffetop(ji,jj)  = zirondep(ji,jj) * xfe_sol / fse3t(ji,jj,jk) 
469               ENDIF
470            ENDDO
471         ENDDO
472      else
473         DO jj = 2,jpjm1
474            DO ji = 2,jpim1
475               IF (tmask(ji,jj,jk) == 1) THEN
476                  ffetop(ji,jj)  = 0.0
477                ENDIF
478            ENDDO
479         ENDDO
480      endif
481      !!
482      !! seafloor iron addition
483      DO jj = 2,jpjm1
484         DO ji = 2,jpim1
485            IF (tmask(ji,jj,jk) == 1) THEN
486               !! AXY (10/07/12): amended to only apply sedimentary flux up
487               !! to ~500 m down
488               !! if (jk.eq.(mbathy(ji,jj)-1).AND.jk.lt.i1100) then
489               if ((jk.eq.mbathy(ji,jj)).AND.jk.le.i0500) then
490                  !! Moore et al. (2004) cite a coastal California value of
491                  !! 5 umol/m2/d, but adopt a global value of 2 umol/m2/d
492                  !! for all areas < 1100 m; here we use this latter value
493                  !! but apply it everywhere
494                  !! AXY (21/07/09): actually, let's just apply it below
495                  !! 1100 m (levels 1-37)
496                  ffebot(ji,jj)  = (xfe_sed / fse3t(ji,jj,jk))
497               else
498                  ffebot(ji,jj)  = 0.0
499               endif
500            ENDIF
501         ENDDO
502      ENDDO
503
504      !! AXY (16/12/09): remove iron addition/removal processes
505      !! For the purposes of the quarter degree run, the iron
506      !! cycle is being pegged to the initial condition supplied
507      !! by Mick Follows via restoration with a 30 day period;
508      !! iron addition at the seafloor is still permitted with
509      !! the idea that this extra iron will be removed by the
510      !! restoration away from the source
511      !! ffescav(ji,jj) = 0.0
512      !! ffetop(ji,jj)  = 0.0
513      !! ffebot(ji,jj)  = 0.0
514
515# if defined key_debug_medusa
516      !! report miscellaneous calculations
517      !! report miscellaneous calculations
518      if (idf.eq.1.AND.idfval.eq.1) then
519         DO jj = 2,jpjm1
520            DO ji = 2,jpim1
521               IF (tmask(ji,jj,jk) == 1) THEN
522                  IF (lwp) write (numout,*) '------------------------------'
523                  IF (lwp) write (numout,*) 'xfe_sol  = ', xfe_sol
524                  IF (lwp) write (numout,*) 'xfe_mass = ', xfe_mass
525                  IF (lwp) write (numout,*) 'ffetop(',jk,')  = ', ffetop(ji,jj)
526                  IF (lwp) write (numout,*) 'ffebot(',jk,')  = ', ffebot(ji,jj)
527                  IF (lwp) write (numout,*) 'xFree(',jk,')   = ', xFree(ji,jj)
528                  IF (lwp) write (numout,*) 'ffescav(',jk,') = ', ffescav(ji,jj)
529               ENDIF
530            ENDDO
531         ENDDO
532      endif
533# endif
534
535   END SUBROUTINE iron_chem_scav
536
537#else
538   !!======================================================================
539   !!  Dummy module :                                   No MEDUSA bio-model
540   !!======================================================================
541CONTAINS
542   SUBROUTINE iron_chem_scav( )                    ! Empty routine
543      WRITE(*,*) 'iron_chem_scav: You should not have seen this print! error?'
544   END SUBROUTINE iron_chem_scav
545#endif 
546
547   !!======================================================================
548END MODULE iron_chem_scav_mod
Note: See TracBrowser for help on using the repository browser.