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.
p4zrem.F90 in branches/2011/dev_r2787_PISCES_improvment/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2011/dev_r2787_PISCES_improvment/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zrem.F90 @ 2823

Last change on this file since 2823 was 2823, checked in by cetlod, 13 years ago

Add new parameterisation in PISCES, see ticket #854

  • Property svn:keywords set to Id
File size: 21.0 KB
Line 
1MODULE p4zrem
2   !!======================================================================
3   !!                         ***  MODULE p4zrem  ***
4   !! TOP :   PISCES Compute remineralization/scavenging of organic compounds
5   !!======================================================================
6   !! History :   1.0  !  2004     (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron
9   !!----------------------------------------------------------------------
10#if defined key_pisces
11   !!----------------------------------------------------------------------
12   !!   'key_top'       and                                      TOP models
13   !!   'key_pisces'                                       PISCES bio-model
14   !!----------------------------------------------------------------------
15   !!   p4z_rem       :  Compute remineralization/scavenging of organic compounds
16   !!   p4z_rem_init  :  Initialisation of parameters for remineralisation
17   !!   p4z_rem_alloc :  Allocate remineralisation variables
18   !!----------------------------------------------------------------------
19   USE oce_trc         !  shared variables between ocean and passive tracers
20   USE trc             !  passive tracers common variables
21   USE sms_pisces      !  PISCES Source Minus Sink variables
22   USE p4zopt          !  optical model
23   USE p4zche          !  chemical model
24   USE p4zprod         !  Growth rate of the 2 phyto groups
25   USE p4zmeso         !  Sources and sinks of mesozooplankton
26   USE p4zint          !  interpolation and computation of various fields
27   USE prtctl_trc      !  print control for debugging
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   p4z_rem         ! called in p4zbio.F90
33   PUBLIC   p4z_rem_init    ! called in trcsms_pisces.F90
34   PUBLIC   p4z_rem_alloc
35
36   !! * Shared module variables
37   REAL(wp), PUBLIC ::  xremik    = 0.3_wp     !: remineralisation rate of POC
38   REAL(wp), PUBLIC ::  xremip    = 0.025_wp   !: remineralisation rate of DOC
39   REAL(wp), PUBLIC ::  nitrif    = 0.05_wp    !: NH4 nitrification rate
40   REAL(wp), PUBLIC ::  xsirem    = 0.003_wp   !: remineralisation rate of POC
41   REAL(wp), PUBLIC ::  xsiremlab = 0.025_wp   !: fast remineralisation rate of POC
42   REAL(wp), PUBLIC ::  xsilab    = 0.31_wp    !: fraction of labile biogenic silica
43   REAL(wp), PUBLIC ::  xlam1     = 0.005_wp   !: scavenging rate of Iron
44   REAL(wp), PUBLIC ::  oxymin    = 1.e-6_wp   !: halk saturation constant for anoxia
45   REAL(wp), PUBLIC ::  ligand    = 0.6E-9_wp  !: ligand concentration in the ocean
46
47
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitr     !: denitrification array
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitnh4   !: -    -    -    -   -
50
51
52   !!* Substitution
53#  include "top_substitute.h90"
54   !!----------------------------------------------------------------------
55   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
56   !! $Id$
57   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
58   !!----------------------------------------------------------------------
59CONTAINS
60
61   SUBROUTINE p4z_rem( kt )
62      !!---------------------------------------------------------------------
63      !!                     ***  ROUTINE p4z_rem  ***
64      !!
65      !! ** Purpose :   Compute remineralization/scavenging of organic compounds
66      !!
67      !! ** Method  : - ???
68      !!---------------------------------------------------------------------
69      USE wrk_nemo, ONLY:   wrk_in_use, wrk_not_released
70      USE wrk_nemo, ONLY:   ztempbac => wrk_2d_1
71      USE wrk_nemo, ONLY:   zdepbac  => wrk_3d_2, zolimi => wrk_3d_3, zolimi2 => wrk_3d_4
72      !
73      INTEGER, INTENT(in) ::   kt ! ocean time step
74      !
75      INTEGER  ::   ji, jj, jk
76      REAL(wp) ::   zremip, zremik , zlam1b, zdepbac2
77      REAL(wp) ::   zkeq  , zfeequi, zsiremin, zfesatur
78      REAL(wp) ::   zsatur, zsatur2, znusil, zdep, zfactdep
79      REAL(wp) ::   zbactfer, zorem, zorem2, zofer
80      REAL(wp) ::   zosil, zdenom1, zscave, zaggdfe, zcoag
81#if ! defined key_kriest
82      REAL(wp) ::   zofer2, zdenom, zdenom2
83#endif
84      REAL(wp) ::   zlamfac, zonitr, zstep
85      CHARACTER (len=25) :: charout
86      !!---------------------------------------------------------------------
87
88      IF(  wrk_in_use(2, 1)  .OR.  wrk_in_use(3, 2,3,4)  ) THEN
89         CALL ctl_stop('p4z_rem: requested workspace arrays unavailable')   ;   RETURN
90      ENDIF
91
92       ! Initialisation of temprary arrys
93       zdepbac (:,:,:) = 0._wp
94       zolimi  (:,:,:) = 0._wp
95       zolimi2 (:,:,:) = 0._wp
96       ztempbac(:,:)   = 0._wp
97
98      !  Computation of the mean phytoplankton concentration as
99      !  a crude estimate of the bacterial biomass
100      !   --------------------------------------------------
101      DO jk = 1, jpkm1
102         DO jj = 1, jpj
103            DO ji = 1, jpi
104               zdep = MAX( hmld(ji,jj), heup(ji,jj) )
105               IF( fsdept(ji,jj,jk) < zdep ) THEN
106                  zdepbac(ji,jj,jk) = MIN( 0.7 * ( trn(ji,jj,jk,jpzoo) + 2.* trn(ji,jj,jk,jpmes) ), 4.e-6 )
107                  ztempbac(ji,jj)   = zdepbac(ji,jj,jk)
108               ELSE
109                  zdepbac(ji,jj,jk) = MIN( 1., zdep / fsdept(ji,jj,jk) ) * ztempbac(ji,jj)
110               ENDIF
111            END DO
112         END DO
113      END DO
114
115      DO jk = 1, jpkm1
116         DO jj = 1, jpj
117            DO ji = 1, jpi
118               ! denitrification factor computed from O2 levels
119               nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - trn(ji,jj,jk,jpoxy) )    &
120                  &                                / ( oxymin + trn(ji,jj,jk,jpoxy) )  )
121               nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) )
122            END DO
123         END DO
124      END DO
125
126      DO jk = 1, jpkm1
127         DO jj = 1, jpj
128            DO ji = 1, jpi
129# if defined key_degrad
130               zstep = xstep * facvol(ji,jj,jk)
131# else
132               zstep = xstep
133# endif
134               ! DOC ammonification. Depends on depth, phytoplankton biomass
135               !     and a limitation term which is supposed to be a parameterization
136               !     of the bacterial activity.
137               zremik = xremik * zstep / 1.e-6 * xlimbac(ji,jj,jk) * zdepbac(ji,jj,jk) 
138               zremik = MAX( zremik, 2.e-4 * xstep )
139               !     Ammonification in oxic waters with oxygen consumption
140               !     -----------------------------------------------------
141               zolimi (ji,jj,jk) = zremik * ( 1.- nitrfac(ji,jj,jk) ) * trn(ji,jj,jk,jpdoc) 
142               zolimi2(ji,jj,jk) = MIN( ( trn(ji,jj,jk,jpoxy) - rtrn ) / o2ut, zolimi(ji,jj,jk) ) 
143               !     Ammonification in suboxic waters with denitrification
144               !     -------------------------------------------------------
145               denitr(ji,jj,jk)  = MIN(  ( trn(ji,jj,jk,jpno3) - rtrn ) / rdenit,   &
146                  &                     zremik * nitrfac(ji,jj,jk) * trn(ji,jj,jk,jpdoc)  )
147               !
148               zolimi (ji,jj,jk) = MAX( 0.e0, zolimi (ji,jj,jk) )
149               zolimi2(ji,jj,jk) = MAX( 0.e0, zolimi2(ji,jj,jk) )
150               denitr (ji,jj,jk) = MAX( 0.e0, denitr (ji,jj,jk) )
151               !
152            END DO
153         END DO
154      END DO
155
156
157      DO jk = 1, jpkm1
158         DO jj = 1, jpj
159            DO ji = 1, jpi
160# if defined key_degrad
161               zstep = xstep * facvol(ji,jj,jk)
162# else
163               zstep = xstep
164# endif
165               !    NH4 nitrification to NO3. Ceased for oxygen concentrations
166               !    below 2 umol/L. Inhibited at strong light
167               !    ----------------------------------------------------------
168               zonitr  =nitrif * zstep * trn(ji,jj,jk,jpnh4) / ( 1.+ emoy(ji,jj,jk) ) * ( 1.- nitrfac(ji,jj,jk) ) 
169               denitnh4(ji,jj,jk) = nitrif * zstep * trn(ji,jj,jk,jpnh4) * nitrfac(ji,jj,jk) 
170               !   Update of the tracers trends
171               !   ----------------------------
172               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) - zonitr - denitnh4(ji,jj,jk)
173               tra(ji,jj,jk,jpno3) = tra(ji,jj,jk,jpno3) + zonitr - rdenita * denitnh4(ji,jj,jk)
174               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) - o2nit * zonitr
175               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2 * rno3 * zonitr + rno3 * ( rdenita - 1. ) * denitnh4(ji,jj,jk)
176            END DO
177         END DO
178      END DO
179
180       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
181         WRITE(charout, FMT="('rem1')")
182         CALL prt_ctl_trc_info(charout)
183         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
184       ENDIF
185
186      DO jk = 1, jpkm1
187         DO jj = 1, jpj
188            DO ji = 1, jpi
189
190               !    Bacterial uptake of iron. No iron is available in DOC. So
191               !    Bacteries are obliged to take up iron from the water. Some
192               !    studies (especially at Papa) have shown this uptake to be significant
193               !    ----------------------------------------------------------
194               zdepbac2 = zdepbac(ji,jj,jk) * zdepbac(ji,jj,jk)
195               zbactfer = 20.e-6 * rfact2 * prmax(ji,jj,jk)                                 &
196                  &              * trn(ji,jj,jk,jpfer) / ( 5E-10 + trn(ji,jj,jk,jpfer) )    &
197                  &              * zdepbac2 / ( xkgraz2 + zdepbac(ji,jj,jk) )               &
198                  &              * ( 0.5 + SIGN( 0.5, trn(ji,jj,jk,jpfer) -2.e-11 )  )
199
200               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zbactfer
201#if defined key_kriest
202               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zbactfer
203#else
204               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zbactfer
205#endif
206            END DO
207         END DO
208      END DO
209
210       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
211         WRITE(charout, FMT="('rem2')")
212         CALL prt_ctl_trc_info(charout)
213         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
214       ENDIF
215
216      DO jk = 1, jpkm1
217         DO jj = 1, jpj
218            DO ji = 1, jpi
219# if defined key_degrad
220               zstep = xstep * facvol(ji,jj,jk)
221# else
222               zstep = xstep
223# endif
224               !    POC disaggregation by turbulence and bacterial activity.
225               !    -------------------------------------------------------------
226               zremip = xremip * zstep * tgfunc(ji,jj,jk) * ( 1.- 0.7 * nitrfac(ji,jj,jk) ) 
227
228               !    POC disaggregation rate is reduced in anoxic zone as shown by
229               !    sediment traps data. In oxic area, the exponent of the martin s
230               !    law is around -0.87. In anoxic zone, it is around -0.35. This
231               !    means a disaggregation constant about 0.5 the value in oxic zones
232               !    -----------------------------------------------------------------
233               zorem  = zremip * trn(ji,jj,jk,jppoc)
234               zofer  = zremip * trn(ji,jj,jk,jpsfe)
235#if ! defined key_kriest
236               zorem2 = zremip * trn(ji,jj,jk,jpgoc)
237               zofer2 = zremip * trn(ji,jj,jk,jpbfe)
238#else
239               zorem2 = zremip * trn(ji,jj,jk,jpnum)
240#endif
241
242               !  Update the appropriate tracers trends
243               !  -------------------------------------
244
245               tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zorem
246               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zofer
247#if defined key_kriest
248               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) - zorem
249               tra(ji,jj,jk,jpnum) = tra(ji,jj,jk,jpnum) - zorem2
250               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) - zofer
251#else
252               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + zorem2 - zorem
253               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) - zorem2
254               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zofer2 - zofer
255               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) - zofer2
256#endif
257
258            END DO
259         END DO
260      END DO
261
262       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
263         WRITE(charout, FMT="('rem3')")
264         CALL prt_ctl_trc_info(charout)
265         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
266       ENDIF
267
268      DO jk = 1, jpkm1
269         DO jj = 1, jpj
270            DO ji = 1, jpi
271# if defined key_degrad
272               zstep = xstep * facvol(ji,jj,jk)
273# else
274               zstep = xstep
275# endif
276               !     Remineralization rate of BSi depedant on T and saturation
277               !     ---------------------------------------------------------
278               zsatur   = ( sio3eq(ji,jj,jk) - trn(ji,jj,jk,jpsil) ) / ( sio3eq(ji,jj,jk) + rtrn )
279               zsatur   = MAX( rtrn, zsatur )
280               zsatur2  = zsatur * ( 1. + tsn(ji,jj,jk,jp_tem) / 400.)**4
281               znusil   = 0.225  * ( 1. + tsn(ji,jj,jk,jp_tem) / 15.) * zsatur + 0.775 * zsatur2**9.25
282               zdep     = MAX( hmld(ji,jj), heup(ji,jj) ) 
283               zdep     = MAX( 0., fsdept(ji,jj,jk) - zdep )
284               zfactdep = xsilab * EXP(-( xsiremlab - xsirem ) * zdep / wsbio2 )
285               zsiremin = ( xsiremlab * zfactdep + xsirem * ( 1. - zfactdep ) ) * zstep * znusil
286               zosil    = zsiremin * trn(ji,jj,jk,jpdsi)
287               !
288               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zosil
289               tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) + zosil
290               !
291            END DO
292         END DO
293      END DO
294
295      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
296         WRITE(charout, FMT="('rem4')")
297         CALL prt_ctl_trc_info(charout)
298         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
299       ENDIF
300
301      zfesatur = ligand
302!CDIR NOVERRCHK
303      DO jk = 1, jpkm1
304!CDIR NOVERRCHK
305         DO jj = 1, jpj
306!CDIR NOVERRCHK
307            DO ji = 1, jpi
308# if defined key_degrad
309               zstep = xstep * facvol(ji,jj,jk)
310# else
311               zstep = xstep
312# endif
313               !  Compute de different ratios for scavenging of iron
314               !  --------------------------------------------------
315
316#if  defined key_kriest
317               zdenom1 = trn(ji,jj,jk,jppoc) / &
318           &           ( trn(ji,jj,jk,jppoc) + trn(ji,jj,jk,jpdsi) + trn(ji,jj,jk,jpcal) + rtrn )
319#else
320               zdenom = 1. / ( trn(ji,jj,jk,jppoc) + trn(ji,jj,jk,jpgoc) + trn(ji,jj,jk,jpdsi) + trn(ji,jj,jk,jpcal) + rtrn )
321               zdenom1 = trn(ji,jj,jk,jppoc) * zdenom
322               zdenom2 = trn(ji,jj,jk,jpgoc) * zdenom
323#endif
324               !  scavenging rate of iron. this scavenging rate depends on the load in particles
325               !  on which they are adsorbed. The  parameterization has been taken from studies on Th
326               !     ------------------------------------------------------------
327               zkeq = fekeq(ji,jj,jk)
328               zfeequi = ( -( 1. + zfesatur * zkeq - zkeq * trn(ji,jj,jk,jpfer) )               &
329                  &        + SQRT( ( 1. + zfesatur * zkeq - zkeq * trn(ji,jj,jk,jpfer) )**2       &
330                  &               + 4. * trn(ji,jj,jk,jpfer) * zkeq) ) / ( 2. * zkeq )
331
332#if defined key_kriest
333               zlam1b = 3.e-5 + xlam1 * (  trn(ji,jj,jk,jppoc)                   &
334                  &                      + trn(ji,jj,jk,jpcal) + trn(ji,jj,jk,jpdsi)  ) * 1.e6
335#else
336               zlam1b = 3.e-5 + xlam1 * (  trn(ji,jj,jk,jppoc) + trn(ji,jj,jk,jpgoc)   &
337                  &                      + trn(ji,jj,jk,jpcal) + trn(ji,jj,jk,jpdsi)  ) * 1.e6
338#endif
339               zscave = zfeequi * zlam1b * zstep
340
341               !  Increased scavenging for very high iron concentrations
342               !  found near the coasts due to increased lithogenic particles
343               !  and let say it is unknown processes (precipitation, ...)
344               !  -----------------------------------------------------------
345               zlam1b  = xlam1 * MAX( 0.e0, ( trn(ji,jj,jk,jpfer) * 1.e9 - 1. ) )
346               zcoag   = zfeequi * zlam1b * zstep
347               zlamfac = MAX( 0.e0, ( gphit(ji,jj) + 55.) / 30. )
348               zlamfac = MIN( 1.  , zlamfac )
349               zdep    =  MIN(1., 1000. / fsdept(ji,jj,jk) )
350#if ! defined key_kriest
351               zlam1b = (  80.* ( trn(ji,jj,jk,jpdoc) + 35.e-6 )                           &
352                  &     + 698.*   trn(ji,jj,jk,jppoc) + 1.05e4 * trn(ji,jj,jk,jpgoc)  )    &
353                  &   * xdiss(ji,jj,jk) + 1E-4 * ( 1. - zlamfac ) * zdep
354#else
355               zlam1b = (  80.* (trn(ji,jj,jk,jpdoc) + 35E-6)              &
356                  &     + 698.*  trn(ji,jj,jk,jppoc)  )                    &
357                  &   * xdiss(ji,jj,jk) + 1E-4 * ( 1. - zlamfac ) * zdep
358#endif
359               zaggdfe = zlam1b * zstep * 0.5 * ( trn(ji,jj,jk,jpfer) - zfeequi )
360               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zscave - zaggdfe - zcoag
361#if defined key_kriest
362               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zscave * zdenom1
363#else
364               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zscave * zdenom1
365               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zscave * zdenom2
366#endif
367            END DO
368         END DO
369      END DO
370      !
371
372      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
373         WRITE(charout, FMT="('rem5')")
374         CALL prt_ctl_trc_info(charout)
375         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
376      ENDIF
377
378      !     Update the arrays TRA which contain the biological sources and sinks
379      !     --------------------------------------------------------------------
380
381      DO jk = 1, jpkm1
382         tra(:,:,jk,jppo4) = tra(:,:,jk,jppo4) + zolimi (:,:,jk) + denitr(:,:,jk)
383         tra(:,:,jk,jpnh4) = tra(:,:,jk,jpnh4) + zolimi (:,:,jk) + denitr(:,:,jk)
384         tra(:,:,jk,jpno3) = tra(:,:,jk,jpno3) - denitr (:,:,jk) * rdenit
385         tra(:,:,jk,jpdoc) = tra(:,:,jk,jpdoc) - zolimi (:,:,jk) - denitr(:,:,jk)
386         tra(:,:,jk,jpoxy) = tra(:,:,jk,jpoxy) - zolimi2(:,:,jk) * o2ut
387         tra(:,:,jk,jpdic) = tra(:,:,jk,jpdic) + zolimi (:,:,jk) + denitr(:,:,jk)
388         tra(:,:,jk,jptal) = tra(:,:,jk,jptal) + rno3 * ( zolimi(:,:,jk) + ( rdenit + 1.) * denitr(:,:,jk) )
389      END DO
390
391      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
392         WRITE(charout, FMT="('rem6')")
393         CALL prt_ctl_trc_info(charout)
394         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
395      ENDIF
396      !
397      IF(  wrk_not_released(2, 1)     .OR.   &
398           wrk_not_released(3, 2,3,4)  )   CALL ctl_stop('p4z_rem: failed to release workspace arrays')
399      !
400   END SUBROUTINE p4z_rem
401
402
403   SUBROUTINE p4z_rem_init
404      !!----------------------------------------------------------------------
405      !!                  ***  ROUTINE p4z_rem_init  ***
406      !!
407      !! ** Purpose :   Initialization of remineralization parameters
408      !!
409      !! ** Method  :   Read the nampisrem namelist and check the parameters
410      !!      called at the first timestep
411      !!
412      !! ** input   :   Namelist nampisrem
413      !!
414      !!----------------------------------------------------------------------
415      NAMELIST/nampisrem/ xremik, xremip, nitrif, xsirem, xsiremlab, xsilab,   &
416      &                   xlam1, oxymin, ligand 
417
418      REWIND( numnatp )                     ! read numnat
419      READ  ( numnatp, nampisrem )
420
421      IF(lwp) THEN                         ! control print
422         WRITE(numout,*) ' '
423         WRITE(numout,*) ' Namelist parameters for remineralization, nampisrem'
424         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
425         WRITE(numout,*) '    remineralisation rate of POC              xremip    =', xremip
426         WRITE(numout,*) '    remineralization rate of DOC              xremik    =', xremik
427         WRITE(numout,*) '    remineralization rate of Si               xsirem    =', xsirem
428         WRITE(numout,*) '    fast remineralization rate of Si          xsiremlab =', xsiremlab
429         WRITE(numout,*) '    fraction of labile biogenic silica        xsilab    =', xsilab
430         WRITE(numout,*) '    scavenging rate of Iron                   xlam1     =', xlam1
431         WRITE(numout,*) '    NH4 nitrification rate                    nitrif    =', nitrif
432         WRITE(numout,*) '    halk saturation constant for anoxia       oxymin    =', oxymin
433         WRITE(numout,*) '    ligand concentration in the ocean         ligand    =', ligand
434      ENDIF
435      !
436      nitrfac (:,:,:) = 0._wp
437      denitr  (:,:,:) = 0._wp
438      denitnh4(:,:,:) = 0._wp
439      !
440   END SUBROUTINE p4z_rem_init
441
442
443   INTEGER FUNCTION p4z_rem_alloc()
444      !!----------------------------------------------------------------------
445      !!                     ***  ROUTINE p4z_rem_alloc  ***
446      !!----------------------------------------------------------------------
447      ALLOCATE( denitr(jpi,jpj,jpk), denitnh4(jpi,jpj,jpk), STAT=p4z_rem_alloc )
448      !
449      IF( p4z_rem_alloc /= 0 )   CALL ctl_warn('p4z_rem_alloc: failed to allocate arrays')
450      !
451   END FUNCTION p4z_rem_alloc
452
453#else
454   !!======================================================================
455   !!  Dummy module :                                   No PISCES bio-model
456   !!======================================================================
457CONTAINS
458   SUBROUTINE p4z_rem                    ! Empty routine
459   END SUBROUTINE p4z_rem
460#endif 
461
462   !!======================================================================
463END MODULE p4zrem
Note: See TracBrowser for help on using the repository browser.