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.
p4zlim.F90 in NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zlim.F90 @ 12759

Last change on this file since 12759 was 12759, checked in by aumont, 4 years ago

make parameterizations in PISCES-operationnal more similar to thos of PISCES-QUOTA (prey switching, optimal allocation, size, ...)

File size: 21.1 KB
Line 
1MODULE p4zlim
2   !!======================================================================
3   !!                         ***  MODULE p4zlim  ***
4   !! TOP :   Computes the nutrient limitation terms of phytoplankton
5   !!======================================================================
6   !! History :   1.0  !  2004     (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!             3.4  !  2011-04  (O. Aumont, C. Ethe) Limitation for iron modelled in quota
9   !!----------------------------------------------------------------------
10   !!   p4z_lim        :   Compute the nutrients limitation terms
11   !!   p4z_lim_init   :   Read the namelist
12   !!----------------------------------------------------------------------
13   USE oce_trc         ! Shared ocean-passive tracers variables
14   USE trc             ! Tracers defined
15   USE sms_pisces      ! PISCES variables
16   USE iom             ! I/O manager
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC p4z_lim           ! called in p4zbio.F90
22   PUBLIC p4z_lim_init      ! called in trcsms_pisces.F90
23   PUBLIC p4z_lim_alloc     ! called in trcini_pisces.F90
24
25   !! * Shared module variables
26   REAL(wp), PUBLIC ::  concnno3    !:  NO3, PO4 half saturation   
27   REAL(wp), PUBLIC ::  concdno3    !:  Phosphate half saturation for diatoms 
28   REAL(wp), PUBLIC ::  concnnh4    !:  NH4 half saturation for nanophyto 
29   REAL(wp), PUBLIC ::  concdnh4    !:  NH4 half saturation for diatoms
30   REAL(wp), PUBLIC ::  concnfer    !:  Iron half saturation for nanophyto
31   REAL(wp), PUBLIC ::  concdfer    !:  Iron half saturation for diatoms 
32   REAL(wp), PUBLIC ::  concbno3    !:  NO3 half saturation  for bacteria
33   REAL(wp), PUBLIC ::  concbnh4    !:  NH4 half saturation for bacteria
34   REAL(wp), PUBLIC ::  xsizedia    !:  Minimum size criteria for diatoms
35   REAL(wp), PUBLIC ::  xsizephy    !:  Minimum size criteria for nanophyto
36   REAL(wp), PUBLIC ::  xsizern     !:  Size ratio for nanophytoplankton
37   REAL(wp), PUBLIC ::  xsizerd     !:  Size ratio for diatoms
38   REAL(wp), PUBLIC ::  xksi1       !:  half saturation constant for Si uptake
39   REAL(wp), PUBLIC ::  xksi2       !:  half saturation constant for Si/C
40   REAL(wp), PUBLIC ::  xkdoc       !:  2nd half-sat. of DOC remineralization 
41   REAL(wp), PUBLIC ::  concbfe     !:  Fe half saturation for bacteria
42   REAL(wp), PUBLIC ::  oxymin      !:  half saturation constant for anoxia
43   REAL(wp), PUBLIC ::  qnfelim     !:  optimal Fe quota for nanophyto
44   REAL(wp), PUBLIC ::  qdfelim     !:  optimal Fe quota for diatoms
45   REAL(wp), PUBLIC ::  caco3r      !:  mean rainratio
46
47   !!* Phytoplankton limitation terms
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanono3   !: Nanophyto limitation by NO3
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatno3   !: Diatoms limitation by NO3
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanonh4   !: Nanophyto limitation by NH4
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatnh4   !:  Diatoms limitation by NH4
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanopo4   !: Nanophyto limitation by PO4
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatpo4   !: Diatoms limitation by PO4
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimphy    !: Nutrient limitation term of nanophytoplankton
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdia    !: Nutrient limitation term of diatoms
56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimnfe    !: Nanophyto limitation by Iron
57   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdfe    !: Diatoms limitation by iron
58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimsi     !: Diatoms limitation by Si
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimbac    !: Bacterial limitation term
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimbacl   !: Bacterial limitation term
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concdfe    !: Limitation of diatoms uptake of Fe
62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concnfe    !: Limitation of Nano uptake of Fe
63   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanofer   !: Limitation of Fe uptake by nanophyto
64   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatfer   !: Limitation of Fe uptake by diatoms
65
66   ! Coefficient for iron limitation following Flynn and Hipkin (1999)
67   REAL(wp) ::  xcoef1   = 0.0016  / 55.85 
68   REAL(wp) ::  xcoef2   = 1.21E-5 * 14. / 55.85 / 7.625 * 0.5 * 1.5
69   REAL(wp) ::  xcoef3   = 1.15E-4 * 14. / 55.85 / 7.625 * 0.5 
70
71   !!----------------------------------------------------------------------
72   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
73   !! $Id: p4zlim.F90 10069 2018-08-28 14:12:24Z nicolasmartin $
74   !! Software governed by the CeCILL license (see ./LICENSE)
75   !!----------------------------------------------------------------------
76CONTAINS
77
78   SUBROUTINE p4z_lim( kt, knt )
79      !!---------------------------------------------------------------------
80      !!                     ***  ROUTINE p4z_lim  ***
81      !!
82      !! ** Purpose :   Compute the co-limitations by the various nutrients
83      !!                for the various phytoplankton species
84      !!
85      !! ** Method  : - Limitation follows the Liebieg law of the minimum
86      !!---------------------------------------------------------------------
87      INTEGER, INTENT(in)  :: kt, knt
88      !
89      INTEGER  ::   ji, jj, jk
90      REAL(wp) ::   zlim1, zlim2, zlim3, zlim4, zno3, zferlim, zcoef
91      REAL(wp) ::   z1_trbdia, z1_trbphy, ztem1, ztem2, zetot1, zetot2
92      REAL(wp) ::   zdenom, zratio, zironmin
93      REAL(wp) ::   zconc1d, zconc1dnh4, zconc0n, zconc0nnh4   
94      REAL(wp) ::   fananof, fadiatf, znutlim, zfalim
95      !!---------------------------------------------------------------------
96      !
97      IF( ln_timing )   CALL timing_start('p4z_lim')
98      !
99      sizena(:,:,:) = 0.0  ;  sizeda(:,:,:) = 0.0
100      !
101      DO jk = 1, jpkm1
102         DO jj = 1, jpj
103            DO ji = 1, jpi
104               
105               ! Tuning of the iron concentration to a minimum level that
106               ! is set to the detection limit
107               ! --------------------------------------------------------
108               zno3    = trb(ji,jj,jk,jpno3) / 40.e-6
109               zferlim = MAX( 3e-11 * zno3 * zno3, 5e-12 )
110               zferlim = MIN( zferlim, 7e-11 )
111               trb(ji,jj,jk,jpfer) = MAX( trb(ji,jj,jk,jpfer), zferlim )
112
113               ! Computation of a variable Ks of diatoms taking into account
114               ! that increasing biomass is made of generally bigger cells
115               !------------------------------------------------------------
116               z1_trbphy   = 1. / ( trb(ji,jj,jk,jpphy) + rtrn )
117               z1_trbdia   = 1. / ( trb(ji,jj,jk,jpdia) + rtrn )
118
119               concnfe(ji,jj,jk) = concnfer * sizen(ji,jj,jk)**0.81
120               zconc0n           = concnno3 * sizen(ji,jj,jk)**0.81
121               zconc0nnh4        = concnnh4 * sizen(ji,jj,jk)**0.81
122
123               concdfe(ji,jj,jk) = concdfer * sized(ji,jj,jk)**0.81 
124               zconc1d           = concdno3 * sized(ji,jj,jk)**0.81 
125               zconc1dnh4        = concdnh4 * sized(ji,jj,jk)**0.81 
126
127               ! Computation of the optimal allocation parameters
128               ! Based on the different papers by Pahlow et al., and
129               ! Smith et al.
130               ! ---------------------------------------------------
131
132               ! Nanophytoplankton
133               znutlim = biron(ji,jj,jk) / concnfe(ji,jj,jk)
134               fananof = MAX(0.01, MIN(0.99, 1. / ( SQRT(znutlim) + 1.) ) )
135
136               ! Diatoms
137               znutlim = biron(ji,jj,jk) / concdfe(ji,jj,jk)
138               fadiatf = MAX(0.01, MIN(0.99, 1. / ( SQRT(znutlim) + 1.) ) )
139
140               ! Michaelis-Menten Limitation term by nutrients of
141               ! heterotrophic bacteria
142               ! -------------------------------------------------
143               zdenom = 1. /  ( concbno3 * concbnh4 + concbnh4 * trb(ji,jj,jk,jpno3) + concbno3 * trb(ji,jj,jk,jpnh4) )
144               xnanono3(ji,jj,jk) = trb(ji,jj,jk,jpno3) * concbnh4 * zdenom
145               xnanonh4(ji,jj,jk) = trb(ji,jj,jk,jpnh4) * concbno3 * zdenom
146               !
147               zlim1    = xnanono3(ji,jj,jk) + xnanonh4(ji,jj,jk)
148               zlim2    = trb(ji,jj,jk,jppo4) / ( trb(ji,jj,jk,jppo4) + concbnh4 )
149               zlim3    = trb(ji,jj,jk,jpfer) / ( concbfe + trb(ji,jj,jk,jpfer) )
150               zlim4    = trb(ji,jj,jk,jpdoc) / ( xkdoc   + trb(ji,jj,jk,jpdoc) )
151               ! Xlimbac is used for DOC solubilization whereas xlimbacl
152               ! is used for all the other bacterial-dependent terms
153               ! -------------------------------------------------------
154               xlimbacl(ji,jj,jk) = MIN( zlim1, zlim2, zlim3 )
155               xlimbac (ji,jj,jk) = MIN( zlim1, zlim2, zlim3 ) * zlim4
156
157               ! Michaelis-Menten Limitation term by nutrients: Nanophyto
158               ! --------------------------------------------------------
159               ! Limitation of Fe uptake
160               zfalim = (1.-fananof) / fananof
161               xnanofer(ji,jj,jk) = (1. - fananof) * biron(ji,jj,jk) / ( biron(ji,jj,jk) + zfalim * concnfe(ji,jj,jk) )
162
163               ! Limitation of nanophytoplankton growth
164               zdenom = 1. /  ( zconc0n * zconc0nnh4 + zconc0nnh4 * trb(ji,jj,jk,jpno3) + zconc0n * trb(ji,jj,jk,jpnh4) )
165               xnanono3(ji,jj,jk) = trb(ji,jj,jk,jpno3) * zconc0nnh4 * zdenom
166               xnanonh4(ji,jj,jk) = trb(ji,jj,jk,jpnh4) * zconc0n    * zdenom
167               !
168               zlim1    = xnanono3(ji,jj,jk) + xnanonh4(ji,jj,jk)
169               zlim2    = trb(ji,jj,jk,jppo4) / ( trb(ji,jj,jk,jppo4) + zconc0nnh4 )
170               zratio   = trb(ji,jj,jk,jpnfe) * z1_trbphy 
171
172               ! The minimum iron quota depends on the size of PSU, respiration
173               ! and the reduction of nitrate following the parameterization
174               ! proposed by Flynn and Hipkin (1999)
175               zironmin = xcoef1 * trb(ji,jj,jk,jpnch) * z1_trbphy + xcoef2 * zlim1 + xcoef3 * xnanono3(ji,jj,jk)
176               zlim3    = MAX( 0.,( zratio - zironmin ) / qnfelim )
177               xnanopo4(ji,jj,jk) = zlim2
178               xlimnfe (ji,jj,jk) = MIN( 1., zlim3 )
179               xlimphy (ji,jj,jk) = MIN( zlim1, zlim2, zlim3 )
180               
181               !   Michaelis-Menten Limitation term by nutrients : Diatoms
182               !   -------------------------------------------------------
183               ! Limitation of Fe uptake
184               zfalim = (1.-fadiatf) / fadiatf
185               xdiatfer(ji,jj,jk) = (1. - fadiatf) * biron(ji,jj,jk) / ( biron(ji,jj,jk) + zfalim * concdfe(ji,jj,jk) )
186
187               ! Limitation of diatoms growth
188               zdenom   = 1. / ( zconc1d * zconc1dnh4 + zconc1dnh4 * trb(ji,jj,jk,jpno3) + zconc1d * trb(ji,jj,jk,jpnh4) )
189               xdiatno3(ji,jj,jk) = trb(ji,jj,jk,jpno3) * zconc1dnh4 * zdenom
190               xdiatnh4(ji,jj,jk) = trb(ji,jj,jk,jpnh4) * zconc1d    * zdenom
191               !
192               zlim1    = xdiatno3(ji,jj,jk) + xdiatnh4(ji,jj,jk)
193               zlim2    = trb(ji,jj,jk,jppo4) / ( trb(ji,jj,jk,jppo4) + zconc1dnh4  )
194               zlim3    = trb(ji,jj,jk,jpsil) / ( trb(ji,jj,jk,jpsil) + xksi(ji,jj) )
195               zratio   = trb(ji,jj,jk,jpdfe) * z1_trbdia
196
197               ! The minimum iron quota depends on the size of PSU, respiration
198               ! and the reduction of nitrate following the parameterization
199               ! proposed by Flynn and Hipkin (1999)
200               zironmin = xcoef1 * trb(ji,jj,jk,jpdch) * z1_trbdia + xcoef2 * zlim1 + xcoef3 * xdiatno3(ji,jj,jk)
201               zlim4    = MAX( 0., ( zratio - zironmin ) / qdfelim )
202               xdiatpo4(ji,jj,jk) = zlim2
203               xlimdfe (ji,jj,jk) = MIN( 1., zlim4 )
204               xlimdia (ji,jj,jk) = MIN( zlim1, zlim2, zlim3, zlim4 )
205               xlimsi  (ji,jj,jk) = MIN( zlim1, zlim2, zlim4 )
206           END DO
207         END DO
208      END DO
209
210      ! Size estimation of phytoplankton based on total biomass
211      ! Assumes that larger biomass implies addition of larger cells
212      ! ------------------------------------------------------------
213      DO jk = 1, jpkm1
214         DO jj = 1, jpj
215            DO ji = 1, jpi
216               zcoef = trb(ji,jj,jk,jpphy) - MIN(xsizephy, trb(ji,jj,jk,jpphy) )
217               sizena(ji,jj,jk) = 1. + ( xsizern -1.0 ) * zcoef / ( xsizephy + zcoef )
218               zcoef = trb(ji,jj,jk,jpdia) - MIN(xsizedia, trb(ji,jj,jk,jpdia) )
219               sizeda(ji,jj,jk) = 1. + ( xsizerd - 1.0 ) * zcoef / ( xsizedia + zcoef )
220
221            END DO
222         END DO
223      END DO
224
225
226      ! Compute the fraction of nanophytoplankton that is made of calcifiers
227      ! This is a purely adhoc formulation described in Aumont et al. (2015)
228      ! This fraction depends on nutrient limitation, light, temperature
229      ! --------------------------------------------------------------------
230      DO jk = 1, jpkm1
231         DO jj = 1, jpj
232            DO ji = 1, jpi
233               zlim1 =  ( trb(ji,jj,jk,jpno3) * concnnh4 + trb(ji,jj,jk,jpnh4) * concnno3 )    &
234                  &   / ( concnno3 * concnnh4 + concnnh4 * trb(ji,jj,jk,jpno3) + concnno3 * trb(ji,jj,jk,jpnh4) ) 
235               zlim2  = trb(ji,jj,jk,jppo4) / ( trb(ji,jj,jk,jppo4) + concnnh4 )
236               zlim3  = trb(ji,jj,jk,jpfer) / ( trb(ji,jj,jk,jpfer) +  5.E-11   )
237               ztem1  = MAX( 0., tsn(ji,jj,jk,jp_tem) )
238               ztem2  = tsn(ji,jj,jk,jp_tem) - 10.
239               zetot1 = MAX( 0., etot_ndcy(ji,jj,jk) - 1.) / ( 4. + etot_ndcy(ji,jj,jk) ) 
240               zetot2 = 30. / ( 30. + etot_ndcy(ji,jj,jk) ) 
241
242               xfracal(ji,jj,jk) = caco3r * MIN( zlim1, zlim2, zlim3 )                  &
243                  &                       * ztem1 / ( 0.1 + ztem1 )                     &
244                  &                       * MAX( 1., trb(ji,jj,jk,jpphy) * 1.e6 / 2. )  &
245                  &                       * zetot1 * zetot2               &
246                  &                       * ( 1. + EXP(-ztem2 * ztem2 / 25. ) )         &
247                  &                       * MIN( 1., 50. / ( hmld(ji,jj) + rtrn ) )
248               xfracal(ji,jj,jk) = MIN( 0.8 , xfracal(ji,jj,jk) )
249               xfracal(ji,jj,jk) = MAX( 0.02, xfracal(ji,jj,jk) )
250            END DO
251         END DO
252      END DO
253      !
254      DO jk = 1, jpkm1
255         DO jj = 1, jpj
256            DO ji = 1, jpi
257               ! denitrification factor computed from O2 levels
258               nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - trb(ji,jj,jk,jpoxy) )    &
259                  &                                / ( oxymin + trb(ji,jj,jk,jpoxy) )  )
260               nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) )
261               !
262               ! redox factor computed from NO3 levels
263               nitrfac2(ji,jj,jk) = MAX( 0.e0,       ( 1.E-6 - trb(ji,jj,jk,jpno3) )  &
264                  &                                / ( 1.E-6 + trb(ji,jj,jk,jpno3) ) )
265               nitrfac2(ji,jj,jk) = MIN( 1., nitrfac2(ji,jj,jk) )
266            END DO
267         END DO
268      END DO
269      !
270      IF( lk_iomput .AND. knt == nrdttrc ) THEN        ! save output diagnostics
271        IF( iom_use( "xfracal" ) )   CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! Faction of nanophytoplankton that is calcifiers
272        IF( iom_use( "LNnut"   ) )   CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term
273        IF( iom_use( "LDnut"   ) )   CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term
274        IF( iom_use( "LNFe"    ) )   CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term
275        IF( iom_use( "LDFe"    ) )   CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term
276        IF( iom_use( "SIZEN"   ) )   CALL iom_put( "SIZEN"  , sizen(:,:,:) * tmask(:,:,:) )  ! Iron limitation term
277        IF( iom_use( "SIZED"   ) )   CALL iom_put( "SIZED"  , sized(:,:,:) * tmask(:,:,:) )  ! Iron limitation term
278      ENDIF
279      !
280      IF( ln_timing )   CALL timing_stop('p4z_lim')
281      !
282   END SUBROUTINE p4z_lim
283
284
285   SUBROUTINE p4z_lim_init
286      !!----------------------------------------------------------------------
287      !!                  ***  ROUTINE p4z_lim_init  ***
288      !!
289      !! ** Purpose :   Initialization of the nutrient limitation parameters
290      !!
291      !! ** Method  :   Read the namp4zlim namelist and check the parameters
292      !!      called at the first timestep (nittrc000)
293      !!
294      !! ** input   :   Namelist namp4zlim
295      !!
296      !!----------------------------------------------------------------------
297      INTEGER ::   ios   ! Local integer
298      !
299      NAMELIST/namp4zlim/ concnno3, concdno3, concnnh4, concdnh4, concnfer, concdfer, concbfe,   &
300         &                concbno3, concbnh4, xsizedia, xsizephy, xsizern, xsizerd,          & 
301         &                xksi1, xksi2, xkdoc, qnfelim, qdfelim, caco3r, oxymin
302      !!----------------------------------------------------------------------
303      !
304      IF(lwp) THEN
305         WRITE(numout,*)
306         WRITE(numout,*) 'p4z_lim_init : initialization of nutrient limitations'
307         WRITE(numout,*) '~~~~~~~~~~~~'
308      ENDIF
309      !
310      REWIND( numnatp_ref )              ! Namelist namp4zlim in reference namelist : Pisces nutrient limitation parameters
311      READ  ( numnatp_ref, namp4zlim, IOSTAT = ios, ERR = 901)
312901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zlim in reference namelist' )
313      REWIND( numnatp_cfg )              ! Namelist namp4zlim in configuration namelist : Pisces nutrient limitation parameters
314      READ  ( numnatp_cfg, namp4zlim, IOSTAT = ios, ERR = 902 )
315902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zlim in configuration namelist' )
316      IF(lwm) WRITE( numonp, namp4zlim )
317      !
318      IF(lwp) THEN                         ! control print
319         WRITE(numout,*) '   Namelist : namp4zlim'
320         WRITE(numout,*) '      mean rainratio                           caco3r    = ', caco3r
321         WRITE(numout,*) '      NO3 half saturation of nanophyto         concnno3  = ', concnno3
322         WRITE(numout,*) '      NO3 half saturation of diatoms           concdno3  = ', concdno3
323         WRITE(numout,*) '      NH4 half saturation for phyto            concnnh4  = ', concnnh4
324         WRITE(numout,*) '      NH4 half saturation for diatoms          concdnh4  = ', concdnh4
325         WRITE(numout,*) '      half saturation constant for Si uptake   xksi1     = ', xksi1
326         WRITE(numout,*) '      half saturation constant for Si/C        xksi2     = ', xksi2
327         WRITE(numout,*) '      half-sat. of DOC remineralization        xkdoc     = ', xkdoc
328         WRITE(numout,*) '      Iron half saturation for nanophyto       concnfer  = ', concnfer
329         WRITE(numout,*) '      Iron half saturation for diatoms         concdfer  = ', concdfer
330         WRITE(numout,*) '      size ratio for nanophytoplankton         xsizern   = ', xsizern
331         WRITE(numout,*) '      size ratio for diatoms                   xsizerd   = ', xsizerd
332         WRITE(numout,*) '      NO3 half saturation of bacteria          concbno3  = ', concbno3
333         WRITE(numout,*) '      NH4 half saturation for bacteria         concbnh4  = ', concbnh4
334         WRITE(numout,*) '      Minimum size criteria for diatoms        xsizedia  = ', xsizedia
335         WRITE(numout,*) '      Minimum size criteria for nanophyto      xsizephy  = ', xsizephy
336         WRITE(numout,*) '      Fe half saturation for bacteria          concbfe   = ', concbfe
337         WRITE(numout,*) '      halk saturation constant for anoxia       oxymin   =' , oxymin
338         WRITE(numout,*) '      optimal Fe quota for nano.               qnfelim   = ', qnfelim
339         WRITE(numout,*) '      Optimal Fe quota for diatoms             qdfelim   = ', qdfelim
340      ENDIF
341      !
342      nitrfac (:,:,:) = 0._wp
343      !
344   END SUBROUTINE p4z_lim_init
345
346
347   INTEGER FUNCTION p4z_lim_alloc()
348      !!----------------------------------------------------------------------
349      !!                     ***  ROUTINE p5z_lim_alloc  ***
350      !!----------------------------------------------------------------------
351      USE lib_mpp , ONLY: ctl_stop
352      !!----------------------------------------------------------------------
353
354      !*  Biological arrays for phytoplankton growth
355      ALLOCATE( xnanono3(jpi,jpj,jpk), xdiatno3(jpi,jpj,jpk),       &
356         &      xnanonh4(jpi,jpj,jpk), xdiatnh4(jpi,jpj,jpk),       &
357         &      xnanopo4(jpi,jpj,jpk), xdiatpo4(jpi,jpj,jpk),       &
358         &      xnanofer(jpi,jpj,jpk), xdiatfer(jpi,jpj,jpk),       &
359         &      xlimphy (jpi,jpj,jpk), xlimdia (jpi,jpj,jpk),       &
360         &      xlimnfe (jpi,jpj,jpk), xlimdfe (jpi,jpj,jpk),       &
361         &      xlimbac (jpi,jpj,jpk), xlimbacl(jpi,jpj,jpk),       &
362         &      concnfe (jpi,jpj,jpk), concdfe (jpi,jpj,jpk),       &
363         &      xlimsi  (jpi,jpj,jpk), STAT=p4z_lim_alloc )
364      !
365      IF( p4z_lim_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_lim_alloc : failed to allocate arrays.' )
366      !
367   END FUNCTION p4z_lim_alloc
368
369   !!======================================================================
370END MODULE p4zlim
Note: See TracBrowser for help on using the repository browser.