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 NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/TOP/PISCES/P4Z/p4zrem.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.

  • Property svn:keywords set to Id
File size: 17.8 KB
Line 
1MODULE p4zrem
2   !!======================================================================
3   !!                         ***  MODULE p4zrem  ***
4   !! TOP :   PISCES Compute remineralization/dissolution 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   !!   p4z_rem       :  Compute remineralization/dissolution of organic compounds
11   !!   p4z_rem_init  :  Initialisation of parameters for remineralisation
12   !!   p4z_rem_alloc :  Allocate remineralisation variables
13   !!----------------------------------------------------------------------
14   USE oce_trc         !  shared variables between ocean and passive tracers
15   USE trc             !  passive tracers common variables
16   USE sms_pisces      !  PISCES Source Minus Sink variables
17   USE p4zche          !  chemical model
18   USE p4zprod         !  Growth rate of the 2 phyto groups
19   USE p4zlim
20   USE prtctl_trc      !  print control for debugging
21   USE iom             !  I/O manager
22
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   p4z_rem         ! called in p4zbio.F90
28   PUBLIC   p4z_rem_init    ! called in trcsms_pisces.F90
29   PUBLIC   p4z_rem_alloc
30
31   REAL(wp), PUBLIC ::   xremikc    !: remineralisation rate of DOC
32   REAL(wp), PUBLIC ::   xremikn    !: remineralisation rate of DON
33   REAL(wp), PUBLIC ::   xremikp    !: remineralisation rate of DOP
34   REAL(wp), PUBLIC ::   xremik     !: remineralisation rate of POC
35   REAL(wp), PUBLIC ::   nitrif     !: NH4 nitrification rate
36   REAL(wp), PUBLIC ::   xsirem     !: remineralisation rate of POC
37   REAL(wp), PUBLIC ::   xsiremlab  !: fast remineralisation rate of POC
38   REAL(wp), PUBLIC ::   xsilab     !: fraction of labile biogenic silica
39   REAL(wp), PUBLIC ::   feratb     !: Fe/C quota in bacteria
40   REAL(wp), PUBLIC ::   xkferb     !: Half-saturation constant for bacteria Fe/C
41
42   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitr   !: denitrification array
43
44   !! * Substitutions
45#  include "do_loop_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
48   !! $Id$
49   !! Software governed by the CeCILL license (see ./LICENSE)
50   !!----------------------------------------------------------------------
51CONTAINS
52
53   SUBROUTINE p4z_rem( kt, knt, Kbb, Kmm, Krhs )
54      !!---------------------------------------------------------------------
55      !!                     ***  ROUTINE p4z_rem  ***
56      !!
57      !! ** Purpose :   Compute remineralization/scavenging of organic compounds
58      !!
59      !! ** Method  : - ???
60      !!---------------------------------------------------------------------
61      INTEGER, INTENT(in) ::   kt, knt         ! ocean time step
62      INTEGER, INTENT(in) ::   Kbb, Kmm, Krhs  ! time level indices
63      !
64      INTEGER  ::   ji, jj, jk
65      REAL(wp) ::   zremik, zremikc, zremikn, zremikp, zsiremin, zfact 
66      REAL(wp) ::   zsatur, zsatur2, znusil, znusil2, zdep, zdepmin, zfactdep
67      REAL(wp) ::   zbactfer, zolimit, zonitr, zrfact2
68      REAL(wp) ::   zammonic, zoxyremc, zoxyremn, zoxyremp
69      REAL(wp) ::   zosil, ztem, zdenitnh4, zolimic, zolimin, zolimip, zdenitrn, zdenitrp
70      CHARACTER (len=25) :: charout
71      REAL(wp), DIMENSION(jpi,jpj    ) :: ztempbac
72      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zdepbac, zolimi, zdepprod, zfacsi, zfacsib, zdepeff, zfebact
73      !!---------------------------------------------------------------------
74      !
75      IF( ln_timing )   CALL timing_start('p4z_rem')
76      !
77      ! Initialisation of arrys
78      zdepprod(:,:,:) = 1._wp
79      zdepeff (:,:,:) = 0.3_wp
80      ztempbac(:,:)   = 0._wp
81      zfacsib(:,:,:)  = xsilab / ( 1.0 - xsilab )
82      zfebact(:,:,:)  = 0._wp
83      zfacsi(:,:,:)   = xsilab
84
85      ! Computation of the mean phytoplankton concentration as
86      ! a crude estimate of the bacterial biomass
87      ! this parameterization has been deduced from a model version
88      ! that was modeling explicitely bacteria
89      ! -------------------------------------------------------
90      DO_3D_11_11( 1, jpkm1 )
91         zdep = MAX( hmld(ji,jj), heup(ji,jj) )
92         IF( gdept(ji,jj,jk,Kmm) < zdep ) THEN
93            zdepbac(ji,jj,jk) = MIN( 0.7 * ( tr(ji,jj,jk,jpzoo,Kbb) + 2.* tr(ji,jj,jk,jpmes,Kbb) ), 4.e-6 )
94            ztempbac(ji,jj)   = zdepbac(ji,jj,jk)
95         ELSE
96            zdepmin = MIN( 1., zdep / gdept(ji,jj,jk,Kmm) )
97            zdepbac (ji,jj,jk) = zdepmin**0.683 * ztempbac(ji,jj)
98            zdepprod(ji,jj,jk) = zdepmin**0.273
99            zdepeff (ji,jj,jk) = zdepeff(ji,jj,jk) * zdepmin**0.3
100         ENDIF
101      END_3D
102
103      IF( ln_p4z ) THEN
104         DO_3D_11_11( 1, jpkm1 )
105            ! DOC ammonification. Depends on depth, phytoplankton biomass
106            ! and a limitation term which is supposed to be a parameterization of the bacterial activity.
107            zremik = xremik * xstep / 1.e-6 * xlimbac(ji,jj,jk) * zdepbac(ji,jj,jk) 
108            zremik = MAX( zremik, 2.74e-4 * xstep )
109            ! Ammonification in oxic waters with oxygen consumption
110            ! -----------------------------------------------------
111            zolimit = zremik * ( 1.- nitrfac(ji,jj,jk) ) * tr(ji,jj,jk,jpdoc,Kbb) 
112            zolimi(ji,jj,jk) = MIN( ( tr(ji,jj,jk,jpoxy,Kbb) - rtrn ) / o2ut, zolimit ) 
113            ! Ammonification in suboxic waters with denitrification
114            ! -------------------------------------------------------
115            zammonic = zremik * nitrfac(ji,jj,jk) * tr(ji,jj,jk,jpdoc,Kbb)
116            denitr(ji,jj,jk)  = zammonic * ( 1. - nitrfac2(ji,jj,jk) )
117            denitr(ji,jj,jk)  = MIN( ( tr(ji,jj,jk,jpno3,Kbb) - rtrn ) / rdenit, denitr(ji,jj,jk) )
118            zoxyremc          = zammonic - denitr(ji,jj,jk)
119            !
120            zolimi (ji,jj,jk) = MAX( 0.e0, zolimi (ji,jj,jk) )
121            denitr (ji,jj,jk) = MAX( 0.e0, denitr (ji,jj,jk) )
122            zoxyremc          = MAX( 0.e0, zoxyremc )
123
124            !
125            tr(ji,jj,jk,jppo4,Krhs) = tr(ji,jj,jk,jppo4,Krhs) + zolimi (ji,jj,jk) + denitr(ji,jj,jk) + zoxyremc
126            tr(ji,jj,jk,jpnh4,Krhs) = tr(ji,jj,jk,jpnh4,Krhs) + zolimi (ji,jj,jk) + denitr(ji,jj,jk) + zoxyremc
127            tr(ji,jj,jk,jpno3,Krhs) = tr(ji,jj,jk,jpno3,Krhs) - denitr (ji,jj,jk) * rdenit
128            tr(ji,jj,jk,jpdoc,Krhs) = tr(ji,jj,jk,jpdoc,Krhs) - zolimi (ji,jj,jk) - denitr(ji,jj,jk) - zoxyremc
129            tr(ji,jj,jk,jpoxy,Krhs) = tr(ji,jj,jk,jpoxy,Krhs) - zolimi (ji,jj,jk) * o2ut
130            tr(ji,jj,jk,jpdic,Krhs) = tr(ji,jj,jk,jpdic,Krhs) + zolimi (ji,jj,jk) + denitr(ji,jj,jk) + zoxyremc
131            tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) + rno3 * ( zolimi(ji,jj,jk) + zoxyremc    &
132            &                     + ( rdenit + 1.) * denitr(ji,jj,jk) )
133         END_3D
134      ELSE
135         DO_3D_11_11( 1, jpkm1 )
136            ! DOC ammonification. Depends on depth, phytoplankton biomass
137            ! and a limitation term which is supposed to be a parameterization of the bacterial activity.
138            ! -----------------------------------------------------------------
139            zremik = xstep / 1.e-6 * MAX(0.01, xlimbac(ji,jj,jk)) * zdepbac(ji,jj,jk) 
140            zremik = MAX( zremik, 2.74e-4 * xstep / xremikc )
141
142            zremikc = xremikc * zremik
143            zremikn = xremikn / xremikc
144            zremikp = xremikp / xremikc
145
146            ! Ammonification in oxic waters with oxygen consumption
147            ! -----------------------------------------------------
148            zolimit = zremikc * ( 1.- nitrfac(ji,jj,jk) ) * tr(ji,jj,jk,jpdoc,Kbb) 
149            zolimic = MAX( 0.e0, MIN( ( tr(ji,jj,jk,jpoxy,Kbb) - rtrn ) / o2ut, zolimit ) ) 
150            zolimi(ji,jj,jk) = zolimic
151            zolimin = zremikn * zolimic * tr(ji,jj,jk,jpdon,Kbb) / ( tr(ji,jj,jk,jpdoc,Kbb) + rtrn )
152            zolimip = zremikp * zolimic * tr(ji,jj,jk,jpdop,Kbb) / ( tr(ji,jj,jk,jpdoc,Kbb) + rtrn ) 
153
154            ! Ammonification in suboxic waters with denitrification
155            ! -------------------------------------------------------
156            zammonic = zremikc * nitrfac(ji,jj,jk) * tr(ji,jj,jk,jpdoc,Kbb)
157            denitr(ji,jj,jk)  = zammonic * ( 1. - nitrfac2(ji,jj,jk) )
158            denitr(ji,jj,jk)  = MAX(0., MIN(  ( tr(ji,jj,jk,jpno3,Kbb) - rtrn ) / rdenit, denitr(ji,jj,jk) ) )
159            zoxyremc          = MAX(0., zammonic - denitr(ji,jj,jk))
160            zdenitrn  = zremikn * denitr(ji,jj,jk) * tr(ji,jj,jk,jpdon,Kbb) / ( tr(ji,jj,jk,jpdoc,Kbb) + rtrn )
161            zdenitrp  = zremikp * denitr(ji,jj,jk) * tr(ji,jj,jk,jpdop,Kbb) / ( tr(ji,jj,jk,jpdoc,Kbb) + rtrn )
162            zoxyremn  = zremikn * zoxyremc * tr(ji,jj,jk,jpdon,Kbb) / ( tr(ji,jj,jk,jpdoc,Kbb) + rtrn )
163            zoxyremp  = zremikp * zoxyremc * tr(ji,jj,jk,jpdop,Kbb) / ( tr(ji,jj,jk,jpdoc,Kbb) + rtrn )
164
165            tr(ji,jj,jk,jppo4,Krhs) = tr(ji,jj,jk,jppo4,Krhs) + zolimip + zdenitrp + zoxyremp
166            tr(ji,jj,jk,jpnh4,Krhs) = tr(ji,jj,jk,jpnh4,Krhs) + zolimin + zdenitrn + zoxyremn
167            tr(ji,jj,jk,jpno3,Krhs) = tr(ji,jj,jk,jpno3,Krhs) - denitr(ji,jj,jk) * rdenit
168            tr(ji,jj,jk,jpdoc,Krhs) = tr(ji,jj,jk,jpdoc,Krhs) - zolimic - denitr(ji,jj,jk) - zoxyremc
169            tr(ji,jj,jk,jpdon,Krhs) = tr(ji,jj,jk,jpdon,Krhs) - zolimin - zdenitrn - zoxyremn
170            tr(ji,jj,jk,jpdop,Krhs) = tr(ji,jj,jk,jpdop,Krhs) - zolimip - zdenitrp - zoxyremp
171            tr(ji,jj,jk,jpoxy,Krhs) = tr(ji,jj,jk,jpoxy,Krhs) - zolimic * o2ut
172            tr(ji,jj,jk,jpdic,Krhs) = tr(ji,jj,jk,jpdic,Krhs) + zolimic + denitr(ji,jj,jk) + zoxyremc
173            tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) + rno3 * ( zolimin + zoxyremn + ( rdenit + 1.) * zdenitrn )
174         END_3D
175         !
176      ENDIF
177
178
179      DO_3D_11_11( 1, jpkm1 )
180         ! NH4 nitrification to NO3. Ceased for oxygen concentrations
181         ! below 2 umol/L. Inhibited at strong light
182         ! ----------------------------------------------------------
183         zonitr  = nitrif * xstep * tr(ji,jj,jk,jpnh4,Kbb) * ( 1.- nitrfac(ji,jj,jk) )  &
184         &         / ( 1.+ emoy(ji,jj,jk) ) * ( 1. + fr_i(ji,jj) * emoy(ji,jj,jk) ) 
185         zdenitnh4 = nitrif * xstep * tr(ji,jj,jk,jpnh4,Kbb) * nitrfac(ji,jj,jk)
186         zdenitnh4 = MIN(  ( tr(ji,jj,jk,jpno3,Kbb) - rtrn ) / rdenita, zdenitnh4 ) 
187         ! Update of the tracers trends
188         ! ----------------------------
189         tr(ji,jj,jk,jpnh4,Krhs) = tr(ji,jj,jk,jpnh4,Krhs) - zonitr - zdenitnh4
190         tr(ji,jj,jk,jpno3,Krhs) = tr(ji,jj,jk,jpno3,Krhs) + zonitr - rdenita * zdenitnh4
191         tr(ji,jj,jk,jpoxy,Krhs) = tr(ji,jj,jk,jpoxy,Krhs) - o2nit * zonitr
192         tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) - 2 * rno3 * zonitr + rno3 * ( rdenita - 1. ) * zdenitnh4
193      END_3D
194
195       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
196         WRITE(charout, FMT="('rem1')")
197         CALL prt_ctl_trc_info(charout)
198         CALL prt_ctl_trc(tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm)
199       ENDIF
200
201      DO_3D_11_11( 1, jpkm1 )
202
203         ! Bacterial uptake of iron. No iron is available in DOC. So
204         ! Bacteries are obliged to take up iron from the water. Some
205         ! studies (especially at Papa) have shown this uptake to be significant
206         ! ----------------------------------------------------------
207         zbactfer = feratb *  rfact2 * 0.6_wp / rday * tgfunc(ji,jj,jk) * xlimbacl(ji,jj,jk)     &
208            &              * tr(ji,jj,jk,jpfer,Kbb) / ( xkferb + tr(ji,jj,jk,jpfer,Kbb) )    &
209            &              * zdepprod(ji,jj,jk) * zdepeff(ji,jj,jk) * zdepbac(ji,jj,jk)
210         tr(ji,jj,jk,jpfer,Krhs) = tr(ji,jj,jk,jpfer,Krhs) - zbactfer*0.33
211         tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + zbactfer*0.25
212         tr(ji,jj,jk,jpbfe,Krhs) = tr(ji,jj,jk,jpbfe,Krhs) + zbactfer*0.08
213         zfebact(ji,jj,jk)   = zbactfer * 0.33
214         blim(ji,jj,jk)      = xlimbacl(ji,jj,jk)  * zdepbac(ji,jj,jk) / 1.e-6 * zdepprod(ji,jj,jk)
215      END_3D
216
217       IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
218         WRITE(charout, FMT="('rem2')")
219         CALL prt_ctl_trc_info(charout)
220         CALL prt_ctl_trc(tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm)
221       ENDIF
222
223      ! Initialization of the array which contains the labile fraction
224      ! of bSi. Set to a constant in the upper ocean
225      ! ---------------------------------------------------------------
226
227      DO_3D_11_11( 1, jpkm1 )
228         zdep     = MAX( hmld(ji,jj), heup_01(ji,jj) )
229         zsatur   = MAX( rtrn, ( sio3eq(ji,jj,jk) - tr(ji,jj,jk,jpsil,Kbb) ) / ( sio3eq(ji,jj,jk) + rtrn ) )
230         zsatur2  = ( 1. + ts(ji,jj,jk,jp_tem,Kmm) / 400.)**37
231         znusil   = 0.225  * ( 1. + ts(ji,jj,jk,jp_tem,Kmm) / 15.) * zsatur + 0.775 * zsatur2 * zsatur**9.25
232         ! Remineralization rate of BSi depedant on T and saturation
233         ! ---------------------------------------------------------
234         IF ( gdept(ji,jj,jk,Kmm) > zdep ) THEN
235            zfacsib(ji,jj,jk) = zfacsib(ji,jj,jk-1) * EXP( -0.5 * ( xsiremlab - xsirem )  &
236            &                   * znusil * e3t(ji,jj,jk,Kmm) / wsbio4(ji,jj,jk) )
237            zfacsi(ji,jj,jk)  = zfacsib(ji,jj,jk) / ( 1.0 + zfacsib(ji,jj,jk) )
238            zfacsib(ji,jj,jk) = zfacsib(ji,jj,jk) * EXP( -0.5 * ( xsiremlab - xsirem )    &
239            &                   * znusil * e3t(ji,jj,jk,Kmm) / wsbio4(ji,jj,jk) )
240         ENDIF
241         zsiremin = ( xsiremlab * zfacsi(ji,jj,jk) + xsirem * ( 1. - zfacsi(ji,jj,jk) ) ) * xstep * znusil
242         zosil    = zsiremin * tr(ji,jj,jk,jpgsi,Kbb)
243         !
244         tr(ji,jj,jk,jpgsi,Krhs) = tr(ji,jj,jk,jpgsi,Krhs) - zosil
245         tr(ji,jj,jk,jpsil,Krhs) = tr(ji,jj,jk,jpsil,Krhs) + zosil
246      END_3D
247
248      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
249         WRITE(charout, FMT="('rem3')")
250         CALL prt_ctl_trc_info(charout)
251         CALL prt_ctl_trc(tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm)
252       ENDIF
253
254      IF( knt == nrdttrc ) THEN
255          zrfact2 = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s
256          !
257          IF( iom_use( "REMIN" ) )  THEN !  Remineralisation rate
258             zolimi(:,:,jpk) = 0. ; CALL iom_put( "REMIN"  , zolimi(:,:,:) * tmask(:,:,:) * zrfact2  )
259          ENDIF
260          CALL iom_put( "DENIT"  , denitr(:,:,:) * rdenit * rno3 * tmask(:,:,:) * zrfact2 ) ! Denitrification
261          IF( iom_use( "BACT" ) )  THEN ! Bacterial biomass
262             zdepbac(:,:,jpk) = 0.  ;   CALL iom_put( "BACT", zdepbac(:,:,:) * 1.E6 * tmask(:,:,:) )
263          ENDIF
264          CALL iom_put( "FEBACT" , zfebact(:,:,:) * 1E9 * tmask(:,:,:) * zrfact2  )
265       ENDIF
266      !
267      IF( ln_timing )   CALL timing_stop('p4z_rem')
268      !
269   END SUBROUTINE p4z_rem
270
271
272   SUBROUTINE p4z_rem_init
273      !!----------------------------------------------------------------------
274      !!                  ***  ROUTINE p4z_rem_init  ***
275      !!
276      !! ** Purpose :   Initialization of remineralization parameters
277      !!
278      !! ** Method  :   Read the nampisrem namelist and check the parameters
279      !!      called at the first timestep
280      !!
281      !! ** input   :   Namelist nampisrem
282      !!
283      !!----------------------------------------------------------------------
284      NAMELIST/nampisrem/ xremik, nitrif, xsirem, xsiremlab, xsilab, feratb, xkferb, & 
285         &                xremikc, xremikn, xremikp
286      INTEGER :: ios                 ! Local integer output status for namelist read
287      !!----------------------------------------------------------------------
288      !
289      IF(lwp) THEN
290         WRITE(numout,*)
291         WRITE(numout,*) 'p4z_rem_init : Initialization of remineralization parameters'
292         WRITE(numout,*) '~~~~~~~~~~~~'
293      ENDIF
294      !
295      READ  ( numnatp_ref, nampisrem, IOSTAT = ios, ERR = 901)
296901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisrem in reference namelist' )
297      READ  ( numnatp_cfg, nampisrem, IOSTAT = ios, ERR = 902 )
298902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisrem in configuration namelist' )
299      IF(lwm) WRITE( numonp, nampisrem )
300
301      IF(lwp) THEN                         ! control print
302         WRITE(numout,*) '   Namelist parameters for remineralization, nampisrem'
303         IF( ln_p4z ) THEN
304            WRITE(numout,*) '      remineralization rate of DOC              xremik    =', xremik
305         ELSE
306            WRITE(numout,*) '      remineralization rate of DOC              xremikc   =', xremikc
307            WRITE(numout,*) '      remineralization rate of DON              xremikn   =', xremikn
308            WRITE(numout,*) '      remineralization rate of DOP              xremikp   =', xremikp
309         ENDIF
310         WRITE(numout,*) '      remineralization rate of Si               xsirem    =', xsirem
311         WRITE(numout,*) '      fast remineralization rate of Si          xsiremlab =', xsiremlab
312         WRITE(numout,*) '      fraction of labile biogenic silica        xsilab    =', xsilab
313         WRITE(numout,*) '      NH4 nitrification rate                    nitrif    =', nitrif
314         WRITE(numout,*) '      Bacterial Fe/C ratio                      feratb    =', feratb
315         WRITE(numout,*) '      Half-saturation constant for bact. Fe/C   xkferb    =', xkferb
316      ENDIF
317      !
318      denitr(:,:,:) = 0._wp
319      !
320   END SUBROUTINE p4z_rem_init
321
322
323   INTEGER FUNCTION p4z_rem_alloc()
324      !!----------------------------------------------------------------------
325      !!                     ***  ROUTINE p4z_rem_alloc  ***
326      !!----------------------------------------------------------------------
327      ALLOCATE( denitr(jpi,jpj,jpk), STAT=p4z_rem_alloc )
328      !
329      IF( p4z_rem_alloc /= 0 )   CALL ctl_stop( 'STOP', 'p4z_rem_alloc: failed to allocate arrays' )
330      !
331   END FUNCTION p4z_rem_alloc
332
333   !!======================================================================
334END MODULE p4zrem
Note: See TracBrowser for help on using the repository browser.