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.
p4zmicro.F90 in NEMO/trunk/src/TOP/PISCES/P4Z – NEMO

source: NEMO/trunk/src/TOP/PISCES/P4Z/p4zmicro.F90

Last change on this file was 15459, checked in by cetlod, 2 years ago

Various bug fixes and more comments in PISCES routines ; sette test OK in debug mode, nn_hls=1/2, with tiling ; run.stat unchanged ; of course tracer.stat different

  • Property svn:keywords set to Id
File size: 18.6 KB
Line 
1MODULE p4zmicro
2   !!======================================================================
3   !!                         ***  MODULE p4zmicro  ***
4   !! TOP :   PISCES Compute the sources/sinks for microzooplankton
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_micro      : Compute the sources/sinks for microzooplankton
11   !!   p4z_micro_init : Initialize and read the appropriate namelist
12   !!----------------------------------------------------------------------
13   USE oce_trc         ! shared variables between ocean and passive tracers
14   USE trc             ! passive tracers common variables
15   USE sms_pisces      ! PISCES Source Minus Sink variables
16   USE p4zlim          ! Co-limitations
17   USE p4zprod         ! production
18   USE iom             ! I/O manager
19   USE prtctl          ! print control for debugging
20
21   IMPLICIT NONE
22   PRIVATE
23
24   !! * Shared module variables
25   PUBLIC   p4z_micro         ! called in p4zbio.F90
26   PUBLIC   p4z_micro_init    ! called in trcsms_pisces.F90
27
28   REAL(wp), PUBLIC ::   part        !: part of calcite not dissolved in microzoo guts
29   REAL(wp), PUBLIC ::   xprefc      !: microzoo preference for POC
30   REAL(wp), PUBLIC ::   xprefn      !: microzoo preference for nanophyto
31   REAL(wp), PUBLIC ::   xprefd      !: microzoo preference for diatoms
32   REAL(wp), PUBLIC ::   xthreshdia  !: diatoms feeding threshold for microzooplankton
33   REAL(wp), PUBLIC ::   xthreshphy  !: nanophyto threshold for microzooplankton
34   REAL(wp), PUBLIC ::   xthreshpoc  !: poc threshold for microzooplankton
35   REAL(wp), PUBLIC ::   xthresh     !: feeding threshold for microzooplankton
36   REAL(wp), PUBLIC ::   resrat      !: exsudation rate of microzooplankton
37   REAL(wp), PUBLIC ::   mzrat       !: microzooplankton mortality rate
38   REAL(wp), PUBLIC ::   grazrat     !: maximal microzoo grazing rate
39   REAL(wp), PUBLIC ::   xkgraz      !: Half-saturation constant of assimilation
40   REAL(wp), PUBLIC ::   unass       !: Non-assimilated part of food
41   REAL(wp), PUBLIC ::   sigma1      !: Fraction of microzoo excretion as DOM
42   REAL(wp), PUBLIC ::   epsher      !: growth efficiency for grazing 1
43   REAL(wp), PUBLIC ::   epshermin   !: minimum growth efficiency for grazing 1
44   REAL(wp), PUBLIC ::   xsigma      !: Width of the grazing window
45   REAL(wp), PUBLIC ::   xsigmadel   !: Maximum additional width of the grazing window at low food density
46
47   !! * Substitutions
48#  include "do_loop_substitute.h90"
49   !!----------------------------------------------------------------------
50   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
51   !! $Id$
52   !! Software governed by the CeCILL license (see ./LICENSE)
53   !!----------------------------------------------------------------------
54CONTAINS
55
56   SUBROUTINE p4z_micro( kt, knt, Kbb, Krhs )
57      !!---------------------------------------------------------------------
58      !!                     ***  ROUTINE p4z_micro  ***
59      !!
60      !! ** Purpose :   Compute the sources/sinks for microzooplankton
61      !!                This includes ingestion and assimilation, flux feeding
62      !!                and mortality. We use a passive prey switching 
63      !!                parameterization.
64      !!                All living compartments smaller than microzooplankton
65      !!                are potential preys of microzooplankton
66      !!
67      !! ** Method  : - ???
68      !!---------------------------------------------------------------------
69      INTEGER, INTENT(in) ::   kt    ! ocean time step
70      INTEGER, INTENT(in) ::   knt   ! ???
71      INTEGER, INTENT(in) ::   Kbb, Krhs  ! time level indices
72      !
73      INTEGER  :: ji, jj, jk
74      REAL(wp) :: zcompadi, zcompaz , zcompaph, zcompapoc
75      REAL(wp) :: zgraze  , zdenom, zdenom2, zfact, zfood, zfoodlim, zbeta
76      REAL(wp) :: zepsherf, zepshert, zepsherq, zepsherv, zgrarsig, zgraztotc, zgraztotn, zgraztotf
77      REAL(wp) :: zgrarem, zgrafer, zgrapoc, zprcaca, zmortz
78      REAL(wp) :: zrespz, ztortz, zgrasratf, zgrasratn
79      REAL(wp) :: zgraznc, zgrazpoc, zgrazdc, zgrazpof, zgrazdf, zgraznf
80      REAL(wp) :: zsigma, zdiffdn, ztmp1, ztmp2, ztmp3, ztmptot, zproport
81      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo
82      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zzligprod
83      CHARACTER (len=25) :: charout
84
85      !!---------------------------------------------------------------------
86      !
87      IF( ln_timing )   CALL timing_start('p4z_micro')
88      !
89      IF (ln_ligand) THEN
90         ALLOCATE( zzligprod(jpi,jpj,jpk) )
91         zzligprod(:,:,:) = 0._wp
92      ENDIF
93      !
94      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1)
95         zcompaz = MAX( ( tr(ji,jj,jk,jpzoo,Kbb) - 1.e-9 ), 0.e0 )
96         zfact   = xstep * tgfunc2(ji,jj,jk) * zcompaz
97
98         ! Proportion of diatoms that are within the size range
99         ! accessible to microzooplankton.
100         zproport  = min(1.0, exp(-1.1 * MAX(0., ( sized(ji,jj,jk) - 1.8 ))**0.8 ))
101
102         !  linear mortality of mesozooplankton
103         !  A michaelis menten modulation term is used to avoid extinction of
104         !  microzooplankton at very low food concentrations. Mortality is
105         !  enhanced in low O2 waters
106         !  -----------------------------------------------------------------
107         zrespz = resrat * zfact * tr(ji,jj,jk,jpzoo,Kbb) / ( xkmort + tr(ji,jj,jk,jpzoo,Kbb) )  &
108            &   + resrat * zfact * 3. * nitrfac(ji,jj,jk)
109
110         !  Zooplankton quadratic mortality. A square function has been selected with
111         !  to mimic predation and disease (density dependent mortality). It also tends
112         !  to stabilise the model
113         !  -------------------------------------------------------------------------
114         ztortz = mzrat * 1.e6 * zfact * tr(ji,jj,jk,jpzoo,Kbb) * (1. - nitrfac(ji,jj,jk))
115
116         !   Computation of the abundance of the preys
117         !   A threshold can be specified in the namelist
118         !   Diatoms have a specific treatment. WHen concentrations
119         !   exceed a certain value, diatoms are suppposed to be too
120         !   big for microzooplankton.
121         !   --------------------------------------------------------
122         zcompadi  = zproport * MAX( ( tr(ji,jj,jk,jpdia,Kbb) - xthreshdia ), 0.e0 )
123         zcompaph  = MAX( ( tr(ji,jj,jk,jpphy,Kbb) - xthreshphy ), 0.e0 )
124         zcompapoc = MAX( ( tr(ji,jj,jk,jppoc,Kbb) - xthreshpoc ), 0.e0 )
125 
126         ! Microzooplankton grazing
127         ! The total amount of food is the sum of all preys accessible to mesozooplankton
128         ! multiplied by their food preference
129         ! A threshold can be specified in the namelist (xthresh). However, when food
130         ! concentration is close to this threshold, it is decreased to avoid the
131         ! accumulation of food in the mesozoopelagic domain
132         ! -------------------------------------------------------------------------------
133         zfood     = xprefn * zcompaph + xprefc * zcompapoc + xprefd * zcompadi
134         zfoodlim  = MAX( 0. , zfood - min(xthresh,0.5*zfood) )
135         zdenom    = zfoodlim / ( xkgraz + zfoodlim )
136         zdenom2   = zdenom / ( zfood + rtrn )
137         zgraze    = grazrat * xstep * tgfunc2(ji,jj,jk) * tr(ji,jj,jk,jpzoo,Kbb) * (1. - nitrfac(ji,jj,jk))
138
139         ! An active switching parameterization is used here.
140         ! We don't use the KTW parameterization proposed by
141         ! Vallina et al. because it tends to produce too steady biomass
142         ! composition and the variance of Chl is too low as it grazes
143         ! too strongly on winning organisms. We use a generalized
144         ! switching parameterization proposed by Morozov and
145         ! Petrovskii (2013)
146         ! ------------------------------------------------------------ 
147         ! The width of the selection window is increased when preys
148         ! have low abundance, .i.e. zooplankton become less specific
149         ! to avoid starvation.
150         ! ----------------------------------------------------------
151         zsigma = 1.0 - zdenom**2/(0.05**2+zdenom**2)
152         zsigma = xsigma + xsigmadel * zsigma
153         zdiffdn = exp( -ABS(log(1.67 * sizen(ji,jj,jk) / (5.0 * sized(ji,jj,jk) + rtrn )) )**2 / zsigma**2)
154         ztmp1 = xprefn * zcompaph * ( zcompaph + zdiffdn * zcompadi ) / ( 1.0 + zdiffdn )
155         ztmp2 = xprefd * zcompadi * ( zdiffdn * zcompaph + zcompadi ) / ( 1.0 + zdiffdn )
156         ztmp3 = xprefc * zcompapoc**2
157         ztmptot = ztmp1 + ztmp2 + ztmp3 + rtrn
158         ztmp1 = ztmp1 / ztmptot
159         ztmp2 = ztmp2 / ztmptot
160         ztmp3 = ztmp3 / ztmptot
161
162         ! Ingestion terms on the different preys of microzooplankton
163         zgraznc   = zgraze   * ztmp1 * zdenom  ! Nanophytoplankton
164         zgrazdc   = zgraze   * ztmp2 * zdenom  ! Diatoms
165         zgrazpoc  = zgraze   * ztmp3 * zdenom  ! POC
166
167         ! Ingestion terms on the iron content of the different preys
168         zgraznf   = zgraznc  * tr(ji,jj,jk,jpnfe,Kbb) / (tr(ji,jj,jk,jpphy,Kbb) + rtrn)
169         zgrazpof  = zgrazpoc * tr(ji,jj,jk,jpsfe,Kbb) / (tr(ji,jj,jk,jppoc,Kbb) + rtrn)
170         zgrazdf   = zgrazdc  * tr(ji,jj,jk,jpdfe,Kbb) / (tr(ji,jj,jk,jpdia,Kbb) + rtrn)
171         !
172         ! Total ingestion rate in C, Fe, N units
173         zgraztotc = zgraznc + zgrazpoc + zgrazdc
174         zgraztotf = zgraznf + zgrazdf  + zgrazpof 
175         zgraztotn = zgraznc * quotan(ji,jj,jk) + zgrazpoc + zgrazdc * quotad(ji,jj,jk)
176
177         ! Grazing by microzooplankton
178         zgrazing(ji,jj,jk) = zgraztotc
179
180
181         ! Microzooplankton efficiency.
182         ! We adopt a formulation proposed by Mitra et al. (2007)
183         ! The gross growth efficiency is controled by the most limiting nutrient.
184         ! Growth is also further decreased when the food quality is poor. This is currently
185         ! hard coded : it can be decreased by up to 50% (zepsherq)
186         ! GGE can also be decreased when food quantity is high, zepsherf (Montagnes and
187         ! Fulton, 2012)
188         ! -----------------------------------------------------------------------------
189
190         zgrasratf = ( zgraztotf + rtrn ) / ( zgraztotc + rtrn )
191         zgrasratn = ( zgraztotn + rtrn ) / ( zgraztotc + rtrn )
192         zepshert  =  MIN( 1., zgrasratn, zgrasratf / feratz)
193         zbeta     = MAX(0., (epsher - epshermin) )
194         ! Food quantity deprivation of the GGE
195         zepsherf  = epshermin + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta )
196         ! Food quality deprivation of the GGE
197         zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 )
198         ! Actual GGE of microzooplankton
199         zepsherv  = zepsherf * zepshert * zepsherq
200         ! Excretion of Fe
201         zgrafer   = zgraztotc * MAX( 0. , ( 1. - unass ) * zgrasratf - feratz * zepsherv ) 
202         ! Excretion of C, N, P
203         zgrarem   = zgraztotc * ( 1. - zepsherv - unass )
204         ! Egestion of C, N, P
205         zgrapoc   = zgraztotc * unass
206
207
208         !  Update of the TRA arrays
209         !  ------------------------
210         ! Fraction of excretion as inorganic nutrients and DIC
211         zgrarsig  = zgrarem * sigma1
212         tr(ji,jj,jk,jppo4,Krhs) = tr(ji,jj,jk,jppo4,Krhs) + zgrarsig
213         tr(ji,jj,jk,jpnh4,Krhs) = tr(ji,jj,jk,jpnh4,Krhs) + zgrarsig
214         tr(ji,jj,jk,jpdoc,Krhs) = tr(ji,jj,jk,jpdoc,Krhs) + zgrarem - zgrarsig
215         !
216         IF( ln_ligand ) THEN
217            tr(ji,jj,jk,jplgw,Krhs) = tr(ji,jj,jk,jplgw,Krhs) + (zgrarem - zgrarsig) * ldocz
218            zzligprod(ji,jj,jk) = (zgrarem - zgrarsig) * ldocz
219         ENDIF
220         !
221         tr(ji,jj,jk,jpoxy,Krhs) = tr(ji,jj,jk,jpoxy,Krhs) - o2ut * zgrarsig
222         tr(ji,jj,jk,jpfer,Krhs) = tr(ji,jj,jk,jpfer,Krhs) + zgrafer
223         zfezoo(ji,jj,jk)    = zgrafer
224         tr(ji,jj,jk,jppoc,Krhs) = tr(ji,jj,jk,jppoc,Krhs) + zgrapoc
225         prodpoc(ji,jj,jk)   = prodpoc(ji,jj,jk) + zgrapoc
226         tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + zgraztotf * unass
227         tr(ji,jj,jk,jpdic,Krhs) = tr(ji,jj,jk,jpdic,Krhs) + zgrarsig
228         tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) + rno3 * zgrarsig
229         !   Update the arrays TRA which contain the biological sources and sinks
230         !   --------------------------------------------------------------------
231         zmortz = ztortz + zrespz
232         tr(ji,jj,jk,jpzoo,Krhs) = tr(ji,jj,jk,jpzoo,Krhs) - zmortz + zepsherv * zgraztotc 
233         tr(ji,jj,jk,jpphy,Krhs) = tr(ji,jj,jk,jpphy,Krhs) - zgraznc
234         tr(ji,jj,jk,jpdia,Krhs) = tr(ji,jj,jk,jpdia,Krhs) - zgrazdc
235         tr(ji,jj,jk,jpnch,Krhs) = tr(ji,jj,jk,jpnch,Krhs) - zgraznc * tr(ji,jj,jk,jpnch,Kbb)/(tr(ji,jj,jk,jpphy,Kbb)+rtrn)
236         tr(ji,jj,jk,jpdch,Krhs) = tr(ji,jj,jk,jpdch,Krhs) - zgrazdc * tr(ji,jj,jk,jpdch,Kbb)/(tr(ji,jj,jk,jpdia,Kbb)+rtrn)
237         tr(ji,jj,jk,jpdsi,Krhs) = tr(ji,jj,jk,jpdsi,Krhs) - zgrazdc * tr(ji,jj,jk,jpdsi,Kbb)/(tr(ji,jj,jk,jpdia,Kbb)+rtrn)
238         tr(ji,jj,jk,jpgsi,Krhs) = tr(ji,jj,jk,jpgsi,Krhs) + zgrazdc * tr(ji,jj,jk,jpdsi,Kbb)/(tr(ji,jj,jk,jpdia,Kbb)+rtrn)
239         tr(ji,jj,jk,jpnfe,Krhs) = tr(ji,jj,jk,jpnfe,Krhs) - zgraznf
240         tr(ji,jj,jk,jpdfe,Krhs) = tr(ji,jj,jk,jpdfe,Krhs) - zgrazdf
241         tr(ji,jj,jk,jppoc,Krhs) = tr(ji,jj,jk,jppoc,Krhs) + zmortz - zgrazpoc
242         prodpoc(ji,jj,jk) = prodpoc(ji,jj,jk) + zmortz
243         conspoc(ji,jj,jk) = conspoc(ji,jj,jk) - zgrazpoc
244         tr(ji,jj,jk,jpsfe,Krhs) = tr(ji,jj,jk,jpsfe,Krhs) + feratz * zmortz - zgrazpof
245         !
246         ! Calcite remineralization due to zooplankton activity
247         ! part of the ingested calcite is not dissolving in the acidic gut
248         ! ----------------------------------------------------------------
249         zprcaca = xfracal(ji,jj,jk) * zgraznc
250         prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo)
251
252         !
253         zprcaca = part * zprcaca
254         tr(ji,jj,jk,jpdic,Krhs) = tr(ji,jj,jk,jpdic,Krhs) - zprcaca
255         tr(ji,jj,jk,jptal,Krhs) = tr(ji,jj,jk,jptal,Krhs) - 2. * zprcaca
256         tr(ji,jj,jk,jpcal,Krhs) = tr(ji,jj,jk,jpcal,Krhs) + zprcaca
257      END_3D
258      !
259      IF( lk_iomput .AND. knt == nrdttrc ) THEN
260        IF( iom_use("GRAZ1") ) THEN  !   Total grazing of phyto by zooplankton
261           zgrazing(:,:,jpk) = 0._wp   ; CALL iom_put( "GRAZ1" , zgrazing(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) ) 
262         ENDIF
263         IF( iom_use("FEZOO") ) THEN 
264           zfezoo (:,:,jpk) = 0._wp    ; CALL iom_put( "FEZOO", zfezoo(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) )
265         ENDIF
266         IF( ln_ligand ) THEN
267            zzligprod(:,:,jpk) = 0._wp ; CALL iom_put( "LPRODZ", zzligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:))
268         ENDIF
269      ENDIF
270      !
271      IF(sn_cfctl%l_prttrc) THEN      ! print mean trends (used for debugging)
272         WRITE(charout, FMT="('micro')")
273         CALL prt_ctl_info( charout, cdcomp = 'top' )
274         CALL prt_ctl(tab4d_1=tr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm)
275      ENDIF
276      !
277      IF( ln_timing )   CALL timing_stop('p4z_micro')
278      !
279   END SUBROUTINE p4z_micro
280
281
282   SUBROUTINE p4z_micro_init
283      !!----------------------------------------------------------------------
284      !!                  ***  ROUTINE p4z_micro_init  ***
285      !!
286      !! ** Purpose :   Initialization of microzooplankton parameters
287      !!
288      !! ** Method  :   Read the namp4zzoo namelist and check the parameters
289      !!                called at the first timestep (nittrc000)
290      !!
291      !! ** input   :   Namelist namp4zzoo
292      !!
293      !!----------------------------------------------------------------------
294      INTEGER ::   ios   ! Local integer
295      !
296      NAMELIST/namp4zzoo/ part, grazrat, resrat, mzrat, xprefn, xprefc, &
297         &                xprefd,  xthreshdia,  xthreshphy,  xthreshpoc, &
298         &                xthresh, xkgraz, epsher, epshermin, sigma1, unass,  &
299         &                xsigma, xsigmadel
300      !!----------------------------------------------------------------------
301      !
302      IF(lwp) THEN
303         WRITE(numout,*) 
304         WRITE(numout,*) 'p4z_micro_init : Initialization of microzooplankton parameters'
305         WRITE(numout,*) '~~~~~~~~~~~~~~'
306      ENDIF
307      !
308      READ  ( numnatp_ref, namp4zzoo, IOSTAT = ios, ERR = 901)
309901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zzoo in reference namelist' )
310
311      READ  ( numnatp_cfg, namp4zzoo, IOSTAT = ios, ERR = 902 )
312902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zzoo in configuration namelist' )
313      IF(lwm) WRITE( numonp, namp4zzoo )
314      !
315      IF(lwp) THEN                         ! control print
316         WRITE(numout,*) '   Namelist : namp4zzoo'
317         WRITE(numout,*) '      part of calcite not dissolved in microzoo guts  part        =', part
318         WRITE(numout,*) '      microzoo preference for POC                     xprefc      =', xprefc
319         WRITE(numout,*) '      microzoo preference for nano                    xprefn      =', xprefn
320         WRITE(numout,*) '      microzoo preference for diatoms                 xprefd      =', xprefd
321         WRITE(numout,*) '      diatoms feeding threshold  for microzoo         xthreshdia  =', xthreshdia
322         WRITE(numout,*) '      nanophyto feeding threshold for microzoo        xthreshphy  =', xthreshphy
323         WRITE(numout,*) '      poc feeding threshold for microzoo              xthreshpoc  =', xthreshpoc
324         WRITE(numout,*) '      feeding threshold for microzooplankton          xthresh     =', xthresh
325         WRITE(numout,*) '      exsudation rate of microzooplankton             resrat      =', resrat
326         WRITE(numout,*) '      microzooplankton mortality rate                 mzrat       =', mzrat
327         WRITE(numout,*) '      maximal microzoo grazing rate                   grazrat     =', grazrat
328         WRITE(numout,*) '      non assimilated fraction of P by microzoo       unass       =', unass
329         WRITE(numout,*) '      Efficicency of microzoo growth                  epsher      =', epsher
330         WRITE(numout,*) '      Minimum efficicency of microzoo growth          epshermin   =', epshermin
331         WRITE(numout,*) '      Fraction of microzoo excretion as DOM           sigma1      =', sigma1
332         WRITE(numout,*) '      half saturation constant for grazing 1          xkgraz      =', xkgraz
333         WRITE(numout,*) '      Width of the grazing window                     xsigma      =', xsigma
334         WRITE(numout,*) '      Maximum additional width of the grazing window  xsigmadel   =', xsigmadel
335
336      ENDIF
337      !
338   END SUBROUTINE p4z_micro_init
339
340   !!======================================================================
341END MODULE p4zmicro
Note: See TracBrowser for help on using the repository browser.