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/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/p4zmicro.F90 @ 13233

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

update of the PISCES comments

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