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/2012/dev_NOC_2012_rev3555/NEMOGCM/NEMO/TOP_SRC/PISCES – NEMO

source: branches/2012/dev_NOC_2012_rev3555/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zrem.F90 @ 3625

Last change on this file since 3625 was 3625, checked in by acc, 11 years ago

Branch dev_NOC_2012_r3555. #1006. Step 7. Check in code now merged with dev_r3385_NOCS04_HAMF

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