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_r11943_MERGE_2019/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zlim.F90 @ 12340

Last change on this file since 12340 was 12340, checked in by acc, 4 years ago

Branch 2019/dev_r11943_MERGE_2019. This commit introduces basic do loop macro
substitution to the 2019 option 1, merge branch. These changes have been SETTE
tested. The only addition is the do_loop_substitute.h90 file in the OCE directory but
the macros defined therein are used throughout the code to replace identifiable, 2D-
and 3D- nested loop opening and closing statements with single-line alternatives. Code
indents are also adjusted accordingly.

The following explanation is taken from comments in the new header file:

This header file contains preprocessor definitions and macros used in the do-loop
substitutions introduced between version 4.0 and 4.2. The primary aim of these macros
is to assist in future applications of tiling to improve performance. This is expected
to be achieved by alternative versions of these macros in selected locations. The
initial introduction of these macros simply replaces all identifiable nested 2D- and
3D-loops with single line statements (and adjusts indenting accordingly). Do loops
are identifiable if they comform to either:

DO jk = ....

DO jj = .... DO jj = ...

DO ji = .... DO ji = ...
. OR .
. .

END DO END DO

END DO END DO

END DO

and white-space variants thereof.

Additionally, only loops with recognised jj and ji loops limits are treated; these are:
Lower limits of 1, 2 or fs_2
Upper limits of jpi, jpim1 or fs_jpim1 (for ji) or jpj, jpjm1 or fs_jpjm1 (for jj)

The macro naming convention takes the form: DO_2D_BT_LR where:

B is the Bottom offset from the PE's inner domain;
T is the Top offset from the PE's inner domain;
L is the Left offset from the PE's inner domain;
R is the Right offset from the PE's inner domain

So, given an inner domain of 2,jpim1 and 2,jpjm1, a typical example would replace:

DO jj = 2, jpj

DO ji = 1, jpim1
.
.

END DO

END DO

with:

DO_2D_01_10
.
.
END_2D

similar conventions apply to the 3D loops macros. jk loop limits are retained
through macro arguments and are not restricted. This includes the possibility of
strides for which an extra set of DO_3DS macros are defined.

In the example definition below the inner PE domain is defined by start indices of
(kIs, kJs) and end indices of (kIe, KJe)

#define DO_2D_00_00 DO jj = kJs, kJe ; DO ji = kIs, kIe
#define END_2D END DO ; END DO

TO DO:


Only conventional nested loops have been identified and replaced by this step. There are constructs such as:

DO jk = 2, jpkm1

z2d(:,:) = z2d(:,:) + e3w(:,:,jk,Kmm) * z3d(:,:,jk) * wmask(:,:,jk)

END DO

which may need to be considered.

File size: 17.2 KB
Line 
1MODULE p4zlim
2   !!======================================================================
3   !!                         ***  MODULE p4zlim  ***
4   !! TOP :   PISCES
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   
22   PUBLIC p4z_lim_init   
23   PUBLIC p4z_lim_alloc
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 phyto 
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   !: ???
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatno3   !: ???
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanonh4   !: ???
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatnh4   !: ???
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xnanopo4   !: ???
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xdiatpo4   !: ???
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimphy    !: ???
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdia    !: ???
56   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimnfe    !: ???
57   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimdfe    !: ???
58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimsi     !: ???
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimbac    !: ??
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   xlimbacl   !: ??
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concdfe    !: ???
62   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)  ::   concnfe    !: ???
63
64   ! Coefficient for iron limitation
65   REAL(wp) ::  xcoef1   = 0.0016  / 55.85 
66   REAL(wp) ::  xcoef2   = 1.21E-5 * 14. / 55.85 / 7.625 * 0.5 * 1.5
67   REAL(wp) ::  xcoef3   = 1.15E-4 * 14. / 55.85 / 7.625 * 0.5 
68
69   !! * Substitutions
70#  include "do_loop_substitute.h90"
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, Kbb, Kmm )
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  : - ???
86      !!---------------------------------------------------------------------
87      INTEGER, INTENT(in)  :: kt, knt
88      INTEGER, INTENT(in)  :: Kbb, Kmm      ! time level indices
89      !
90      INTEGER  ::   ji, jj, jk
91      REAL(wp) ::   zlim1, zlim2, zlim3, zlim4, zno3, zferlim
92      REAL(wp) ::   zconcd, zconcd2, zconcn, zconcn2
93      REAL(wp) ::   z1_trbdia, z1_trbphy, ztem1, ztem2, zetot1, zetot2
94      REAL(wp) ::   zdenom, zratio, zironmin
95      REAL(wp) ::   zconc1d, zconc1dnh4, zconc0n, zconc0nnh4   
96      !!---------------------------------------------------------------------
97      !
98      IF( ln_timing )   CALL timing_start('p4z_lim')
99      !
100      DO_3D_11_11( 1, jpkm1 )
101         
102         ! Tuning of the iron concentration to a minimum level that is set to the detection limit
103         !-------------------------------------
104         zno3    = tr(ji,jj,jk,jpno3,Kbb) / 40.e-6
105         zferlim = MAX( 3e-11 * zno3 * zno3, 5e-12 )
106         zferlim = MIN( zferlim, 7e-11 )
107         tr(ji,jj,jk,jpfer,Kbb) = MAX( tr(ji,jj,jk,jpfer,Kbb), zferlim )
108
109         ! Computation of a variable Ks for iron on diatoms taking into account
110         ! that increasing biomass is made of generally bigger cells
111         !------------------------------------------------
112         zconcd   = MAX( 0.e0 , tr(ji,jj,jk,jpdia,Kbb) - xsizedia )
113         zconcd2  = tr(ji,jj,jk,jpdia,Kbb) - zconcd
114         zconcn   = MAX( 0.e0 , tr(ji,jj,jk,jpphy,Kbb) - xsizephy )
115         zconcn2  = tr(ji,jj,jk,jpphy,Kbb) - zconcn
116         z1_trbphy   = 1. / ( tr(ji,jj,jk,jpphy,Kbb) + rtrn )
117         z1_trbdia   = 1. / ( tr(ji,jj,jk,jpdia,Kbb) + rtrn )
118
119         concdfe(ji,jj,jk) = MAX( concdfer, ( zconcd2 * concdfer + concdfer * xsizerd * zconcd ) * z1_trbdia )
120         zconc1d           = MAX( concdno3, ( zconcd2 * concdno3 + concdno3 * xsizerd * zconcd ) * z1_trbdia )
121         zconc1dnh4        = MAX( concdnh4, ( zconcd2 * concdnh4 + concdnh4 * xsizerd * zconcd ) * z1_trbdia )
122
123         concnfe(ji,jj,jk) = MAX( concnfer, ( zconcn2 * concnfer + concnfer * xsizern * zconcn ) * z1_trbphy )
124         zconc0n           = MAX( concnno3, ( zconcn2 * concnno3 + concnno3 * xsizern * zconcn ) * z1_trbphy )
125         zconc0nnh4        = MAX( concnnh4, ( zconcn2 * concnnh4 + concnnh4 * xsizern * zconcn ) * z1_trbphy )
126
127         ! Michaelis-Menten Limitation term for nutrients Small bacteria
128         ! -------------------------------------------------------------
129         zdenom = 1. /  ( concbno3 * concbnh4 + concbnh4 * tr(ji,jj,jk,jpno3,Kbb) + concbno3 * tr(ji,jj,jk,jpnh4,Kbb) )
130         xnanono3(ji,jj,jk) = tr(ji,jj,jk,jpno3,Kbb) * concbnh4 * zdenom
131         xnanonh4(ji,jj,jk) = tr(ji,jj,jk,jpnh4,Kbb) * concbno3 * zdenom
132         !
133         zlim1    = xnanono3(ji,jj,jk) + xnanonh4(ji,jj,jk)
134         zlim2    = tr(ji,jj,jk,jppo4,Kbb) / ( tr(ji,jj,jk,jppo4,Kbb) + concbnh4 )
135         zlim3    = tr(ji,jj,jk,jpfer,Kbb) / ( concbfe + tr(ji,jj,jk,jpfer,Kbb) )
136         zlim4    = tr(ji,jj,jk,jpdoc,Kbb) / ( xkdoc   + tr(ji,jj,jk,jpdoc,Kbb) )
137         xlimbacl(ji,jj,jk) = MIN( zlim1, zlim2, zlim3 )
138         xlimbac (ji,jj,jk) = MIN( zlim1, zlim2, zlim3 ) * zlim4
139
140         ! Michaelis-Menten Limitation term for nutrients Small flagellates
141         ! -----------------------------------------------
142         zdenom = 1. /  ( zconc0n * zconc0nnh4 + zconc0nnh4 * tr(ji,jj,jk,jpno3,Kbb) + zconc0n * tr(ji,jj,jk,jpnh4,Kbb) )
143         xnanono3(ji,jj,jk) = tr(ji,jj,jk,jpno3,Kbb) * zconc0nnh4 * zdenom
144         xnanonh4(ji,jj,jk) = tr(ji,jj,jk,jpnh4,Kbb) * zconc0n    * zdenom
145         !
146         zlim1    = xnanono3(ji,jj,jk) + xnanonh4(ji,jj,jk)
147         zlim2    = tr(ji,jj,jk,jppo4,Kbb) / ( tr(ji,jj,jk,jppo4,Kbb) + zconc0nnh4 )
148         zratio   = tr(ji,jj,jk,jpnfe,Kbb) * z1_trbphy 
149         zironmin = xcoef1 * tr(ji,jj,jk,jpnch,Kbb) * z1_trbphy + xcoef2 * zlim1 + xcoef3 * xnanono3(ji,jj,jk)
150         zlim3    = MAX( 0.,( zratio - zironmin ) / qnfelim )
151         xnanopo4(ji,jj,jk) = zlim2
152         xlimnfe (ji,jj,jk) = MIN( 1., zlim3 )
153         xlimphy (ji,jj,jk) = MIN( zlim1, zlim2, zlim3 )
154         !
155         !   Michaelis-Menten Limitation term for nutrients Diatoms
156         !   ----------------------------------------------
157         zdenom   = 1. / ( zconc1d * zconc1dnh4 + zconc1dnh4 * tr(ji,jj,jk,jpno3,Kbb) + zconc1d * tr(ji,jj,jk,jpnh4,Kbb) )
158         xdiatno3(ji,jj,jk) = tr(ji,jj,jk,jpno3,Kbb) * zconc1dnh4 * zdenom
159         xdiatnh4(ji,jj,jk) = tr(ji,jj,jk,jpnh4,Kbb) * zconc1d    * zdenom
160         !
161         zlim1    = xdiatno3(ji,jj,jk) + xdiatnh4(ji,jj,jk)
162         zlim2    = tr(ji,jj,jk,jppo4,Kbb) / ( tr(ji,jj,jk,jppo4,Kbb) + zconc1dnh4  )
163         zlim3    = tr(ji,jj,jk,jpsil,Kbb) / ( tr(ji,jj,jk,jpsil,Kbb) + xksi(ji,jj) )
164         zratio   = tr(ji,jj,jk,jpdfe,Kbb) * z1_trbdia
165         zironmin = xcoef1 * tr(ji,jj,jk,jpdch,Kbb) * z1_trbdia + xcoef2 * zlim1 + xcoef3 * xdiatno3(ji,jj,jk)
166         zlim4    = MAX( 0., ( zratio - zironmin ) / qdfelim )
167         xdiatpo4(ji,jj,jk) = zlim2
168         xlimdfe (ji,jj,jk) = MIN( 1., zlim4 )
169         xlimdia (ji,jj,jk) = MIN( zlim1, zlim2, zlim3, zlim4 )
170         xlimsi  (ji,jj,jk) = MIN( zlim1, zlim2, zlim4 )
171      END_3D
172
173      ! Compute the fraction of nanophytoplankton that is made of calcifiers
174      ! --------------------------------------------------------------------
175      DO_3D_11_11( 1, jpkm1 )
176         zlim1 =  ( tr(ji,jj,jk,jpno3,Kbb) * concnnh4 + tr(ji,jj,jk,jpnh4,Kbb) * concnno3 )    &
177            &   / ( concnno3 * concnnh4 + concnnh4 * tr(ji,jj,jk,jpno3,Kbb) + concnno3 * tr(ji,jj,jk,jpnh4,Kbb) ) 
178         zlim2  = tr(ji,jj,jk,jppo4,Kbb) / ( tr(ji,jj,jk,jppo4,Kbb) + concnnh4 )
179         zlim3  = tr(ji,jj,jk,jpfer,Kbb) / ( tr(ji,jj,jk,jpfer,Kbb) +  5.E-11   )
180         ztem1  = MAX( 0., ts(ji,jj,jk,jp_tem,Kmm) )
181         ztem2  = ts(ji,jj,jk,jp_tem,Kmm) - 10.
182         zetot1 = MAX( 0., etot_ndcy(ji,jj,jk) - 1.) / ( 4. + etot_ndcy(ji,jj,jk) ) 
183         zetot2 = 30. / ( 30. + etot_ndcy(ji,jj,jk) ) 
184
185         xfracal(ji,jj,jk) = caco3r * MIN( zlim1, zlim2, zlim3 )                  &
186            &                       * ztem1 / ( 0.1 + ztem1 )                     &
187            &                       * MAX( 1., tr(ji,jj,jk,jpphy,Kbb) * 1.e6 / 2. )  &
188            &                       * zetot1 * zetot2               &
189            &                       * ( 1. + EXP(-ztem2 * ztem2 / 25. ) )         &
190            &                       * MIN( 1., 50. / ( hmld(ji,jj) + rtrn ) )
191         xfracal(ji,jj,jk) = MIN( 0.8 , xfracal(ji,jj,jk) )
192         xfracal(ji,jj,jk) = MAX( 0.02, xfracal(ji,jj,jk) )
193      END_3D
194      !
195      DO_3D_11_11( 1, jpkm1 )
196         ! denitrification factor computed from O2 levels
197         nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - tr(ji,jj,jk,jpoxy,Kbb) )    &
198            &                                / ( oxymin + tr(ji,jj,jk,jpoxy,Kbb) )  )
199         nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) )
200         !
201         ! denitrification factor computed from NO3 levels
202         nitrfac2(ji,jj,jk) = MAX( 0.e0,       ( 1.E-6 - tr(ji,jj,jk,jpno3,Kbb) )  &
203            &                                / ( 1.E-6 + tr(ji,jj,jk,jpno3,Kbb) ) )
204         nitrfac2(ji,jj,jk) = MIN( 1., nitrfac2(ji,jj,jk) )
205      END_3D
206      !
207      IF( lk_iomput .AND. knt == nrdttrc ) THEN        ! save output diagnostics
208        CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht
209        CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term
210        CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term
211        CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term
212        CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term
213      ENDIF
214      !
215      IF( ln_timing )   CALL timing_stop('p4z_lim')
216      !
217   END SUBROUTINE p4z_lim
218
219
220   SUBROUTINE p4z_lim_init
221      !!----------------------------------------------------------------------
222      !!                  ***  ROUTINE p4z_lim_init  ***
223      !!
224      !! ** Purpose :   Initialization of nutrient limitation parameters
225      !!
226      !! ** Method  :   Read the nampislim namelist and check the parameters
227      !!      called at the first timestep (nittrc000)
228      !!
229      !! ** input   :   Namelist nampislim
230      !!
231      !!----------------------------------------------------------------------
232      INTEGER ::   ios   ! Local integer
233      !
234      NAMELIST/namp4zlim/ concnno3, concdno3, concnnh4, concdnh4, concnfer, concdfer, concbfe,   &
235         &                concbno3, concbnh4, xsizedia, xsizephy, xsizern, xsizerd,          & 
236         &                xksi1, xksi2, xkdoc, qnfelim, qdfelim, caco3r, oxymin
237      !!----------------------------------------------------------------------
238      !
239      IF(lwp) THEN
240         WRITE(numout,*)
241         WRITE(numout,*) 'p4z_lim_init : initialization of nutrient limitations'
242         WRITE(numout,*) '~~~~~~~~~~~~'
243      ENDIF
244      !
245      READ  ( numnatp_ref, namp4zlim, IOSTAT = ios, ERR = 901)
246901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zlim in reference namelist' )
247      READ  ( numnatp_cfg, namp4zlim, IOSTAT = ios, ERR = 902 )
248902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zlim in configuration namelist' )
249      IF(lwm) WRITE( numonp, namp4zlim )
250      !
251      IF(lwp) THEN                         ! control print
252         WRITE(numout,*) '   Namelist : namp4zlim'
253         WRITE(numout,*) '      mean rainratio                           caco3r    = ', caco3r
254         WRITE(numout,*) '      NO3 half saturation of nanophyto         concnno3  = ', concnno3
255         WRITE(numout,*) '      NO3 half saturation of diatoms           concdno3  = ', concdno3
256         WRITE(numout,*) '      NH4 half saturation for phyto            concnnh4  = ', concnnh4
257         WRITE(numout,*) '      NH4 half saturation for diatoms          concdnh4  = ', concdnh4
258         WRITE(numout,*) '      half saturation constant for Si uptake   xksi1     = ', xksi1
259         WRITE(numout,*) '      half saturation constant for Si/C        xksi2     = ', xksi2
260         WRITE(numout,*) '      half-sat. of DOC remineralization        xkdoc     = ', xkdoc
261         WRITE(numout,*) '      Iron half saturation for nanophyto       concnfer  = ', concnfer
262         WRITE(numout,*) '      Iron half saturation for diatoms         concdfer  = ', concdfer
263         WRITE(numout,*) '      size ratio for nanophytoplankton         xsizern   = ', xsizern
264         WRITE(numout,*) '      size ratio for diatoms                   xsizerd   = ', xsizerd
265         WRITE(numout,*) '      NO3 half saturation of bacteria          concbno3  = ', concbno3
266         WRITE(numout,*) '      NH4 half saturation for bacteria         concbnh4  = ', concbnh4
267         WRITE(numout,*) '      Minimum size criteria for diatoms        xsizedia  = ', xsizedia
268         WRITE(numout,*) '      Minimum size criteria for nanophyto      xsizephy  = ', xsizephy
269         WRITE(numout,*) '      Fe half saturation for bacteria          concbfe   = ', concbfe
270         WRITE(numout,*) '      halk saturation constant for anoxia       oxymin   =' , oxymin
271         WRITE(numout,*) '      optimal Fe quota for nano.               qnfelim   = ', qnfelim
272         WRITE(numout,*) '      Optimal Fe quota for diatoms             qdfelim   = ', qdfelim
273      ENDIF
274      !
275      nitrfac (:,:,jpk) = 0._wp
276      nitrfac2(:,:,jpk) = 0._wp
277      xfracal (:,:,jpk) = 0._wp
278      xlimphy (:,:,jpk) = 0._wp
279      xlimdia (:,:,jpk) = 0._wp
280      xlimnfe (:,:,jpk) = 0._wp
281      xlimdfe (:,:,jpk) = 0._wp
282      !
283   END SUBROUTINE p4z_lim_init
284
285
286   INTEGER FUNCTION p4z_lim_alloc()
287      !!----------------------------------------------------------------------
288      !!                     ***  ROUTINE p5z_lim_alloc  ***
289      !!----------------------------------------------------------------------
290      USE lib_mpp , ONLY: ctl_stop
291      !!----------------------------------------------------------------------
292
293      !*  Biological arrays for phytoplankton growth
294      ALLOCATE( xnanono3(jpi,jpj,jpk), xdiatno3(jpi,jpj,jpk),       &
295         &      xnanonh4(jpi,jpj,jpk), xdiatnh4(jpi,jpj,jpk),       &
296         &      xnanopo4(jpi,jpj,jpk), xdiatpo4(jpi,jpj,jpk),       &
297         &      xlimphy (jpi,jpj,jpk), xlimdia (jpi,jpj,jpk),       &
298         &      xlimnfe (jpi,jpj,jpk), xlimdfe (jpi,jpj,jpk),       &
299         &      xlimbac (jpi,jpj,jpk), xlimbacl(jpi,jpj,jpk),       &
300         &      concnfe (jpi,jpj,jpk), concdfe (jpi,jpj,jpk),       &
301         &      xlimsi  (jpi,jpj,jpk), STAT=p4z_lim_alloc )
302      !
303      IF( p4z_lim_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_lim_alloc : failed to allocate arrays.' )
304      !
305   END FUNCTION p4z_lim_alloc
306
307   !!======================================================================
308END MODULE p4zlim
Note: See TracBrowser for help on using the repository browser.