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.
p4zmeso.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/p4zmeso.F90 @ 13200

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

minor bug fixes for calcite production and diagnostics

  • Property svn:keywords set to Id
File size: 34.3 KB
Line 
1MODULE p4zmeso
2   !!======================================================================
3   !!                         ***  MODULE p4zmeso  ***
4   !! TOP :   PISCES Compute the sources/sinks for mesozooplankton
5   !!======================================================================
6   !! History :   1.0  !  2002     (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_meso        : Compute the sources/sinks for mesozooplankton
11   !!   p4z_meso_init   : Initialization of the parameters for mesozooplankton
12   !!   p4z_meso_alloc  : Allocate variables for mesozooplankton
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 p4zprod         ! production
18   USE prtctl_trc      ! print control for debugging
19   USE iom             ! I/O manager
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   p4z_meso              ! called in p4zbio.F90
25   PUBLIC   p4z_meso_init         ! called in trcsms_pisces.F90
26   PUBLIC   p4z_meso_alloc        ! called in trcini_pisces.F90
27
28   !! * Shared module variables
29   REAL(wp), PUBLIC ::  part2        !: part of calcite not dissolved in mesozoo guts
30   REAL(wp), PUBLIC ::  xpref2d      !: mesozoo preference for diatoms
31   REAL(wp), PUBLIC ::  xpref2n      !: mesozoo preference for nanophyto
32   REAL(wp), PUBLIC ::  xpref2z      !: mesozoo preference for microzooplankton
33   REAL(wp), PUBLIC ::  xpref2c      !: mesozoo preference for POC
34   REAL(wp), PUBLIC ::  xthresh2zoo  !: zoo feeding threshold for mesozooplankton
35   REAL(wp), PUBLIC ::  xthresh2dia  !: diatoms feeding threshold for mesozooplankton
36   REAL(wp), PUBLIC ::  xthresh2phy  !: nanophyto feeding threshold for mesozooplankton
37   REAL(wp), PUBLIC ::  xthresh2poc  !: poc feeding threshold for mesozooplankton
38   REAL(wp), PUBLIC ::  xthresh2     !: feeding threshold for mesozooplankton
39   REAL(wp), PUBLIC ::  resrat2      !: exsudation rate of mesozooplankton
40   REAL(wp), PUBLIC ::  mzrat2       !: microzooplankton mortality rate
41   REAL(wp), PUBLIC ::  grazrat2     !: maximal mesozoo grazing rate
42   REAL(wp), PUBLIC ::  xkgraz2      !: non assimilated fraction of P by mesozoo
43   REAL(wp), PUBLIC ::  unass2       !: Efficicency of mesozoo growth
44   REAL(wp), PUBLIC ::  sigma2       !: Fraction of mesozoo excretion as DOM
45   REAL(wp), PUBLIC ::  epsher2      !: growth efficiency
46   REAL(wp), PUBLIC ::  epsher2min   !: minimum growth efficiency at high food for grazing 2
47   REAL(wp), PUBLIC ::  grazflux     !: mesozoo flux feeding rate
48   REAL(wp), PUBLIC ::  xfracmig     !: Fractional biomass of meso that performs DVM
49   LOGICAL , PUBLIC ::  ln_dvm_meso  !: Boolean to activate DVM of mesozooplankton
50   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: depmig  !: DVM of mesozooplankton : migration depth
51   INTEGER , ALLOCATABLE, SAVE, DIMENSION(:,:) :: kmig    !: Vertical indice of the the migration depth
52
53   !!----------------------------------------------------------------------
54   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
55   !! $Id$
56   !! Software governed by the CeCILL license (see ./LICENSE)
57   !!----------------------------------------------------------------------
58CONTAINS
59
60   SUBROUTINE p4z_meso( kt, knt )
61      !!---------------------------------------------------------------------
62      !!                     ***  ROUTINE p4z_meso  ***
63      !!
64      !! ** Purpose :   Compute the sources/sinks for mesozooplankton
65      !!                This includes ingestion and assimilation, flux feeding
66      !!                and mortality. We use a passive prey switching 
67      !!                parameterization.
68      !!                All living compartments smaller than mesozooplankton
69      !!                are potential preys of mesozooplankton as well as small
70      !!                sinking particles
71      !!
72      !! ** Method  : - ???
73      !!---------------------------------------------------------------------
74      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step and ???
75      !
76      INTEGER  :: ji, jj, jk, jkt
77      REAL(wp) :: zcompadi, zcompaph, zcompapoc, zcompaz, zcompam
78      REAL(wp) :: zgraze2 , zdenom, zdenom2, zfact   , zfood, zfoodlim, zproport, zbeta
79      REAL(wp) :: zmortzgoc, zfrac, zfracfe, zratio, zratio2, zfracal, zgrazcal
80      REAL(wp) :: zepsherf, zepshert, zepsherq, zepsherv, zgrarsig, zgraztotc, zgraztotn, zgraztotf
81      REAL(wp) :: zmigreltime, zprcaca, zmortz, zgrasratf, zgrasratn
82      REAL(wp) :: zrespz, ztortz, zgrazdc, zgrazz, zgrazpof, zgraznc, zgrazpoc, zgraznf, zgrazdf
83      REAL(wp) :: zgrazfffp, zgrazfffg, zgrazffep, zgrazffeg, zrum, zcodel, zargu, zval
84      REAL(wp) :: zsigma, zdiffdn, ztmp1, ztmp2, ztmp3, ztmp4, ztmptot
85      CHARACTER (len=25) :: charout
86      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo2
87      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrarem, zgraref, zgrapoc, zgrapof, zgrabsi
88      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   zgramigrem, zgramigref, zgramigpoc, zgramigpof
89      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   zstrn, zgramigbsi
90      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zw3d, zz2ligprod
91      !!---------------------------------------------------------------------
92      !
93      IF( ln_timing )   CALL timing_start('p4z_meso')
94      !
95      zgrazing(:,:,:) = 0._wp   ;  zgrapoc(:,:,:) = 0._wp
96      zfezoo2 (:,:,:) = 0._wp   ;  zgrarem(:,:,:) = 0._wp
97      zgraref (:,:,:) = 0._wp   ;  zgrapof(:,:,:) = 0._wp
98      zgrabsi (:,:,:) = 0._wp
99      !
100      IF (ln_ligand) THEN
101         ALLOCATE( zz2ligprod(jpi,jpj,jpk) )
102         zz2ligprod(:,:,:) = 0._wp
103      ENDIF
104      !
105      ! Diurnal vertical migration of mesozooplankton
106      ! Computation of the migration depth
107      ! ---------------------------------------------
108      IF (ln_dvm_meso) CALL p4z_meso_depmig
109      !
110      DO jk = 1, jpk
111         DO jj = 1, jpj
112            DO ji = 1, jpi
113               zcompam   = MAX( ( trb(ji,jj,jk,jpmes) - 1.e-9 ), 0.e0 )
114               zfact     = xstep * tgfunc2(ji,jj,jk) * zcompam
115
116               !  linear mortality of mesozooplankton
117               !  A michaelis menten modulation term is used to avoid extinction of
118               !  mesozooplankton at very low food concentration. Mortality is
119 
120               !  enhanced in low O2 waters
121               !  -----------------------------------------------------------------
122               zrespz    = resrat2 * zfact * ( trb(ji,jj,jk,jpmes) / ( xkmort + trb(ji,jj,jk,jpmes) )  &
123               &           + 3. * nitrfac(ji,jj,jk) )
124
125               !  Zooplankton quadratic mortality. A square function has been selected with
126               !  to mimic predation and disease (density dependent mortality). It also tends
127               !  to stabilise the model
128               !  -------------------------------------------------------------------------
129               ztortz    = mzrat2 * 1.e6 * zfact * trb(ji,jj,jk,jpmes)  * (1. - nitrfac(ji,jj,jk) )
130
131               !   Computation of the abundance of the preys
132               !   A threshold can be specified in the namelist
133               !   --------------------------------------------
134               zcompadi  = MAX( ( trb(ji,jj,jk,jpdia) - xthresh2dia ), 0.e0 )
135               zcompaz   = MAX( ( trb(ji,jj,jk,jpzoo) - xthresh2zoo ), 0.e0 )
136               zcompapoc = MAX( ( trb(ji,jj,jk,jppoc) - xthresh2poc ), 0.e0 )
137               ! Size effect of nanophytoplankton on grazing : the smaller it is, the less prone
138               ! it is to predation by mesozooplankton. We use a quota dependant parameterization
139               ! as a low quota indicates oligotrophic conditions which are charatcerized by
140               ! small cells
141               ! -------------------------------------------------------------------------------
142               zcompaph  = MAX( ( trb(ji,jj,jk,jpphy) - xthresh2phy ), 0.e0 ) &
143                  &      * MIN(1., MAX( 0., ( quotan(ji,jj,jk) - 0.2) / 0.3 ) )
144
145               ! Mesozooplankton grazing
146               ! The total amount of food is the sum of all preys accessible to mesozooplankton
147               ! multiplied by their food preference
148               ! A threshold can be specified in the namelist (xthresh2). However, when food
149               ! concentration is close to this threshold, it is decreased to avoid the
150               ! accumulation of food in the mesozoopelagic domain
151               ! -------------------------------------------------------------------------------
152               zfood     = xpref2d * zcompadi + xpref2z * zcompaz + xpref2n * zcompaph + xpref2c * zcompapoc 
153               zfoodlim  = MAX( 0., zfood - MIN( 0.5 * zfood, xthresh2 ) )
154               zdenom    = zfoodlim / ( xkgraz2 + zfoodlim )
155               zdenom2   = zdenom / ( zfood + rtrn )
156               zgraze2   = grazrat2 * xstep * tgfunc2(ji,jj,jk) * trb(ji,jj,jk,jpmes) * (1. - nitrfac(ji,jj,jk)) 
157
158               ! An active switching parameterization is used here.
159               ! We don't use the KTW parameterization proposed by
160               ! Vallina et al. because it tends to produce too steady biomass
161               ! composition and the variance of Chl is too low as it grazes
162               ! too strongly on winning organisms. We use a generalized
163               ! switching parameterization proposed by Morozov and
164               ! Petrovskii (2013)
165               ! ------------------------------------------------------------ 
166               ! The width of the selection window is increased when preys
167               ! have low abundance, .i.e. zooplankton become less specific
168               ! to avoid starvation.
169               ! ----------------------------------------------------------
170               zsigma = 1.0 - zdenom**2/(0.05**2+zdenom**2)
171               zsigma = 0.5 + 1.0 * zsigma
172               ! Nanophytoplankton and diatoms are the only preys considered
173               ! to be close enough to have potential interference
174               ! -----------------------------------------------------------
175               zdiffdn = exp( -ABS(log(1.67 * sizen(ji,jj,jk) / (5.0 * sized(ji,jj,jk) + rtrn )) )**2 / zsigma**2 )
176               ztmp1 = xpref2n * zcompaph * ( zcompaph + zdiffdn * zcompadi ) / ( 1.0 + zdiffdn )
177               ztmp2 = xpref2c * zcompapoc**2
178               ztmp3 = xpref2d * zcompadi * ( zdiffdn * zcompadi + zcompaph ) / ( 1.0 + zdiffdn )
179               ztmp4 = xpref2z * zcompaz**2
180               ztmptot = ztmp1 + ztmp2 + ztmp3 + ztmp4 + rtrn
181               ztmp1 = ztmp1 / ztmptot
182               ztmp2 = ztmp2 / ztmptot
183               ztmp3 = ztmp3 / ztmptot
184               ztmp4 = ztmp4 / ztmptot
185
186               !   Mesozooplankton regular grazing on the different preys
187               !   ------------------------------------------------------
188               zgrazdc   = zgraze2  * ztmp3 * zdenom
189               zgraznc   = zgraze2  * ztmp1 * zdenom
190               zgrazpoc  = zgraze2  * ztmp2 * zdenom
191               zgrazz    = zgraze2  * ztmp4 * zdenom
192
193               zgraznf   = zgraznc  * trb(ji,jj,jk,jpnfe) / ( trb(ji,jj,jk,jpphy) + rtrn)
194               zgrazdf   = zgrazdc  * trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) + rtrn)
195               zgrazpof  = zgrazpoc * trb(ji,jj,jk,jpsfe) / ( trb(ji,jj,jk,jppoc) + rtrn)
196
197               !  Mesozooplankton flux feeding on GOC and POC. The feeding pressure
198               ! is proportional to the flux
199               !  ------------------------------------------------------------------
200               zgrazffeg = grazflux  * xstep * wsbio4(ji,jj,jk)      &
201               &           * tgfunc2(ji,jj,jk) * trb(ji,jj,jk,jpgoc) * trb(ji,jj,jk,jpmes) &
202               &           * (1. - nitrfac(ji,jj,jk))
203               zgrazfffg = zgrazffeg * trb(ji,jj,jk,jpbfe) / (trb(ji,jj,jk,jpgoc) + rtrn)
204               zgrazffep = grazflux  * xstep *  wsbio3(ji,jj,jk)     &
205               &           * tgfunc2(ji,jj,jk) * trb(ji,jj,jk,jppoc) * trb(ji,jj,jk,jpmes) &
206               &           * (1. - nitrfac(ji,jj,jk))
207               zgrazfffp = zgrazffep * trb(ji,jj,jk,jpsfe) / (trb(ji,jj,jk,jppoc) + rtrn)
208               
209               zgraztotc = zgrazdc + zgrazz + zgraznc + zgrazpoc + zgrazffep + zgrazffeg
210               ! Compute the proportion of filter feeders. It is assumed steady state.
211               ! --------------------------------------------------------------------- 
212               zproport  = (zgrazffep + zgrazffeg)/(rtrn + zgraztotc)
213
214               ! Compute fractionation of aggregates. It is assumed that
215               ! diatoms based aggregates are more prone to fractionation
216               ! since they are more porous (marine snow instead of fecal pellets)
217               ! -----------------------------------------------------------------
218               zratio    = trb(ji,jj,jk,jpgsi) / ( trb(ji,jj,jk,jpgoc) + rtrn )
219               zratio2   = zratio * zratio
220               zfrac     = zproport * grazflux  * xstep * wsbio4(ji,jj,jk)      &
221               &          * trb(ji,jj,jk,jpgoc) * trb(ji,jj,jk,jpmes)          &
222               &          * ( 0.2 + 3.8 * zratio2 / ( 1.**2 + zratio2 ) )
223               zfracfe   = zfrac * trb(ji,jj,jk,jpbfe) / (trb(ji,jj,jk,jpgoc) + rtrn)
224
225               ! Flux feeding is multiplied by the fractional biomass of flux feeders
226               zgrazffep = zproport * zgrazffep
227               zgrazffeg = zproport * zgrazffeg
228               zgrazfffp = zproport * zgrazfffp
229               zgrazfffg = zproport * zgrazfffg
230               zgraztotc = zgrazdc + zgrazz + zgraznc + zgrazpoc + zgrazffep + zgrazffeg
231               zgraztotn = zgrazdc * quotad(ji,jj,jk) + zgrazz + zgraznc * quotan(ji,jj,jk)   &
232               &   + zgrazpoc + zgrazffep + zgrazffeg
233               zgraztotf = zgrazdf + zgraznf + zgrazz * ferat3 + zgrazpof + zgrazfffp + zgrazfffg
234
235               ! Total grazing ( grazing by microzoo is already computed in p4zmicro )
236               zgrazing(ji,jj,jk) = zgraztotc
237
238               ! Mesozooplankton efficiency.
239               ! We adopt a formulation proposed by Mitra et al. (2007)
240               ! The gross growth efficiency is controled by the most limiting nutrient.
241               ! Growth is also further decreased when the food quality is poor. This is currently
242               ! hard coded : it can be decreased by up to 50% (zepsherq)
243               ! GGE can also be decreased when food quantity is high, zepsherf (Montagnes and
244               ! Fulton, 2012)
245               ! -----------------------------------------------------------------------------------
246               zgrasratf =  ( zgraztotf + rtrn )/ ( zgraztotc + rtrn )
247               zgrasratn =  ( zgraztotn + rtrn )/ ( zgraztotc + rtrn )
248               zepshert  = MIN( 1., zgrasratn, zgrasratf / ferat3)
249               zbeta     = MAX(0., (epsher2 - epsher2min) )
250               zepsherf  = epsher2min + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta ) 
251               zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 )
252               zepsherv  = zepsherf * zepshert * zepsherq
253               !
254               ! Impact of grazing on the prognostic variables
255               ! ---------------------------------------------
256               zmortz = ztortz + zrespz
257               ! Mortality induced by the upper trophic levels, ztortz, is allocated
258               ! according to a infinite chain of predators (ANderson et al., 2013)
259               zmortzgoc = unass2 / ( 1. - epsher2 ) * ztortz + zrespz
260               tra(ji,jj,jk,jpmes) = tra(ji,jj,jk,jpmes) - zmortz + zepsherv * zgraztotc
261               tra(ji,jj,jk,jpdia) = tra(ji,jj,jk,jpdia) - zgrazdc
262               tra(ji,jj,jk,jpzoo) = tra(ji,jj,jk,jpzoo) - zgrazz
263               tra(ji,jj,jk,jpphy) = tra(ji,jj,jk,jpphy) - zgraznc
264               tra(ji,jj,jk,jpnch) = tra(ji,jj,jk,jpnch) - zgraznc * trb(ji,jj,jk,jpnch) / ( trb(ji,jj,jk,jpphy) + rtrn )
265               tra(ji,jj,jk,jpdch) = tra(ji,jj,jk,jpdch) - zgrazdc * trb(ji,jj,jk,jpdch) / ( trb(ji,jj,jk,jpdia) + rtrn )
266               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zgrazdc * trb(ji,jj,jk,jpdsi) / ( trb(ji,jj,jk,jpdia) + rtrn )
267               zgrabsi(ji,jj,jk)   = zgrazdc * trb(ji,jj,jk,jpdsi) / ( trb(ji,jj,jk,jpdia) + rtrn )
268               tra(ji,jj,jk,jpnfe) = tra(ji,jj,jk,jpnfe) - zgraznf
269               tra(ji,jj,jk,jpdfe) = tra(ji,jj,jk,jpdfe) - zgrazdf
270               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) - zgrazpoc - zgrazffep + zfrac
271               prodpoc(ji,jj,jk) = prodpoc(ji,jj,jk) + zfrac
272               conspoc(ji,jj,jk) = conspoc(ji,jj,jk) - zgrazpoc - zgrazffep
273               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) - zgrazffeg - zfrac
274               consgoc(ji,jj,jk) = consgoc(ji,jj,jk) - zgrazffeg - zfrac
275               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) - zgrazpof - zgrazfffp + zfracfe
276               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) - zgrazfffg - zfracfe
277
278               ! Calcite remineralization due to zooplankton activity
279               ! part2 of the ingested calcite is not dissolving in the
280               ! acidic gut
281               ! ------------------------------------------------------
282               zfracal = trb(ji,jj,jk,jpcal) / ( trb(ji,jj,jk,jpgoc) + rtrn )
283               zgrazcal = zgrazffeg * (1. - part2) * zfracal
284               ! calcite production by zooplankton activity
285               zprcaca = xfracal(ji,jj,jk) * zgraznc
286               prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo)
287               !
288               zprcaca = part2 * zprcaca
289               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) + zgrazcal - zprcaca
290               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2. * ( zgrazcal + zprcaca )
291               tra(ji,jj,jk,jpcal) = tra(ji,jj,jk,jpcal) - zgrazcal + zprcaca
292 
293               ! Computation of total excretion and egestion by mesozoo.
294               ! ---------------------------------------------------------
295               zgrarem(ji,jj,jk) = zgraztotc * ( 1. - zepsherv - unass2 ) &
296               &         + ( 1. - epsher2 - unass2 ) / ( 1. - epsher2 ) * ztortz
297               zgraref(ji,jj,jk) = zgraztotc * MAX( 0. , ( 1. - unass2 ) * zgrasratf - ferat3 * zepsherv )    &
298               &         + ferat3 * ( ( 1. - epsher2 - unass2 ) /( 1. - epsher2 ) * ztortz )
299               zgrapoc(ji,jj,jk) = zgraztotc * unass2 + zmortzgoc
300               zgrapof(ji,jj,jk) = zgraztotf * unass2 + ferat3 * zmortzgoc
301            END DO
302         END DO
303      END DO
304
305      ! Computation of the effect of DVM by mesozooplankton
306      ! This part is only activated if ln_dvm_meso is set to true
307      ! The parameterization has been published in Gorgues et al. (2019).
308      ! -----------------------------------------------------------------
309      IF (ln_dvm_meso) THEN
310         ALLOCATE( zgramigrem(jpi,jpj), zgramigref(jpi,jpj), zgramigpoc(jpi,jpj), zgramigpof(jpi,jpj) )
311         ALLOCATE( zgramigbsi(jpi,jpj) )
312         ALLOCATE( zstrn(jpi,jpj) )
313         zgramigrem(:,:) = 0.0    ;   zgramigref(:,:) = 0.0
314         zgramigpoc(:,:) = 0.0    ;   zgramigpof(:,:) = 0.0
315         zgramigbsi(:,:) = 0.0
316
317         ! compute the day length depending on latitude and the day
318         zrum = REAL( nday_year - 80, wp ) / REAL( nyear_len(1), wp )
319         zcodel = ASIN(  SIN( zrum * rpi * 2._wp ) * SIN( rad * 23.5_wp )  )
320
321         ! day length in hours
322         zstrn(:,:) = 0.
323         DO jj = 1, jpj
324            DO ji = 1, jpi
325               zargu = TAN( zcodel ) * TAN( gphit(ji,jj) * rad )
326               zargu = MAX( -1., MIN(  1., zargu ) )
327               zstrn(ji,jj) = MAX( 0.0, 24. - 2. * ACOS( zargu ) / rad / 15. )
328               zstrn(ji,jj) = MIN(0.75, MAX( 0.25, zstrn(ji,jj) / 24.) )
329            END DO
330         END DO
331
332        ! Compute the amount of materials that will go into vertical migration
333        ! This fraction is sumed over the euphotic zone and is removed from
334        ! the fluxes driven by mesozooplankton in the euphotic zone.
335        ! --------------------------------------------------------------------
336         DO jk = 1, jpk
337            DO jj = 1, jpj
338               DO ji = 1, jpi
339                  zmigreltime = (1. - zstrn(ji,jj))
340                  IF ( gdept_n(ji,jj,jk) <= heup(ji,jj) ) THEN
341                     zgramigrem(ji,jj) = zgramigrem(ji,jj) + xfracmig * zgrarem(ji,jj,jk) * (1. - zmigreltime )    &
342                     &                   * e3t_n(ji,jj,jk) * tmask(ji,jj,jk)
343                     zgramigref(ji,jj) = zgramigref(ji,jj) + xfracmig * zgraref(ji,jj,jk) * (1. - zmigreltime )   &
344                     &                   * e3t_n(ji,jj,jk) * tmask(ji,jj,jk)
345                     zgramigpoc(ji,jj) = zgramigpoc(ji,jj) + xfracmig * zgrapoc(ji,jj,jk) * (1. - zmigreltime )   &
346                     &                   * e3t_n(ji,jj,jk) * tmask(ji,jj,jk)
347                     zgramigpof(ji,jj) = zgramigpof(ji,jj) + xfracmig * zgrapof(ji,jj,jk) * (1. - zmigreltime )   &
348                     &                   * e3t_n(ji,jj,jk) * tmask(ji,jj,jk)
349                     zgramigbsi(ji,jj) = zgramigbsi(ji,jj) + xfracmig * zgrabsi(ji,jj,jk) * (1. - zmigreltime )   &
350                     &                   * e3t_n(ji,jj,jk) * tmask(ji,jj,jk)
351
352                     zgrarem(ji,jj,jk) = zgrarem(ji,jj,jk) * ( (1.0 - xfracmig) + xfracmig * zmigreltime )
353                     zgraref(ji,jj,jk) = zgraref(ji,jj,jk) * ( (1.0 - xfracmig) + xfracmig * zmigreltime )
354                     zgrapoc(ji,jj,jk) = zgrapoc(ji,jj,jk) * ( (1.0 - xfracmig) + xfracmig * zmigreltime )
355                     zgrapof(ji,jj,jk) = zgrapof(ji,jj,jk) * ( (1.0 - xfracmig) + xfracmig * zmigreltime )
356                     zgrabsi(ji,jj,jk) = zgrabsi(ji,jj,jk) * ( (1.0 - xfracmig) + xfracmig * zmigreltime )
357                  ENDIF
358               END DO
359            END DO
360         END DO
361     
362         ! The inorganic and organic fluxes induced by migrating organisms are added at the
363         ! the migration depth (corresponding indice is set by kmig)
364         ! --------------------------------------------------------------------------------
365         DO jj = 1, jpj
366            DO ji = 1, jpi
367               IF (tmask(ji,jj,1) == 1.) THEN
368                  jkt = kmig(ji,jj)
369                  zgrarem(ji,jj,jkt) = zgrarem(ji,jj,jkt) + zgramigrem(ji,jj) / e3t_n(ji,jj,jkt) 
370                  zgraref(ji,jj,jkt) = zgraref(ji,jj,jkt) + zgramigref(ji,jj) / e3t_n(ji,jj,jkt)
371                  zgrapoc(ji,jj,jkt) = zgrapoc(ji,jj,jkt) + zgramigpoc(ji,jj) / e3t_n(ji,jj,jkt)
372                  zgrapof(ji,jj,jkt) = zgrapof(ji,jj,jkt) + zgramigpof(ji,jj) / e3t_n(ji,jj,jkt)
373                  zgrabsi(ji,jj,jkt) = zgrabsi(ji,jj,jkt) + zgramigbsi(ji,jj) / e3t_n(ji,jj,jkt)
374               ENDIF
375            END DO
376         END DO
377         !
378         ! Deallocate temporary variables
379         ! ------------------------------
380         DEALLOCATE( zgramigrem, zgramigref, zgramigpoc, zgramigpof, zgramigbsi )
381         DEALLOCATE( zstrn )
382
383      ! End of the ln_dvm_meso part
384      ENDIF
385
386      DO jk = 1, jpk
387         DO jj = 1, jpj
388            DO ji = 1, jpi
389               !   Update the arrays TRA which contain the biological sources and sinks
390               !   This only concerns the variables which are affected by DVM (inorganic
391               !   nutrients, DOC agands, and particulate organic carbon).
392               zgrarsig  = zgrarem(ji,jj,jk) * sigma2
393               tra(ji,jj,jk,jppo4) = tra(ji,jj,jk,jppo4) + zgrarsig
394               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) + zgrarsig
395               tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zgrarem(ji,jj,jk) - zgrarsig
396               !
397               IF( ln_ligand ) THEN
398                  tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + (zgrarem(ji,jj,jk) - zgrarsig) * ldocz
399                  zz2ligprod(ji,jj,jk) = (zgrarem(ji,jj,jk) - zgrarsig) * ldocz
400               ENDIF
401               !
402               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) - o2ut * zgrarsig
403               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zgraref(ji,jj,jk)
404               zfezoo2(ji,jj,jk)   = zgraref(ji,jj,jk)
405               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) + zgrarsig
406               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) + rno3 * zgrarsig             
407               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zgrapoc(ji,jj,jk)
408               prodgoc(ji,jj,jk)   = prodgoc(ji,jj,jk)   + zgrapoc(ji,jj,jk)
409               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zgrapof(ji,jj,jk)
410               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) + zgrabsi(ji,jj,jk)
411            END DO
412         END DO
413      END DO
414      !
415      ! Write the output
416      IF( lk_iomput .AND. knt == nrdttrc ) THEN
417         ALLOCATE( zw3d(jpi,jpj,jpk) )
418         IF( iom_use( "GRAZ2" ) ) THEN
419            zw3d(:,:,:) = zgrazing(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)  !   Total grazing of phyto by zooplankton
420            CALL iom_put( "GRAZ2", zw3d )
421         ENDIF
422         IF( iom_use( "PCAL" ) ) THEN
423            zw3d(:,:,:) = prodcal(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)   !  Calcite production
424            CALL iom_put( "PCAL", zw3d ) 
425         ENDIF
426         IF( iom_use( "FEZOO2" ) ) THEN
427            zw3d(:,:,:) = zfezoo2(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)   !
428            CALL iom_put( "FEZOO2", zw3d )
429         ENDIF
430         IF( iom_use( "LPRODZ2" ) .AND. ln_ligand )  THEN
431            zw3d(:,:,:) = zz2ligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)
432            CALL iom_put( "LPRODZ2"  , zw3d )
433         ENDIF
434         DEALLOCATE( zw3d )
435      ENDIF
436      !
437      IF (ln_ligand)  DEALLOCATE( zz2ligprod )
438      !
439      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
440        WRITE(charout, FMT="('meso')")
441        CALL prt_ctl_trc_info(charout)
442        CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
443      ENDIF
444      !
445      IF( ln_timing )   CALL timing_stop('p4z_meso')
446      !
447   END SUBROUTINE p4z_meso
448
449
450   SUBROUTINE p4z_meso_init
451      !!----------------------------------------------------------------------
452      !!                  ***  ROUTINE p4z_meso_init  ***
453      !!
454      !! ** Purpose :   Initialization of mesozooplankton parameters
455      !!
456      !! ** Method  :   Read the namp4zmes namelist and check the parameters
457      !!      called at the first timestep (nittrc000)
458      !!
459      !! ** input   :   Namelist nampismes
460      !!----------------------------------------------------------------------
461      INTEGER ::   ios   ! Local integer
462      !
463      NAMELIST/namp4zmes/ part2, grazrat2, resrat2, mzrat2, xpref2n, xpref2d, xpref2z,   &
464         &                xpref2c, xthresh2dia, xthresh2phy, xthresh2zoo, xthresh2poc, &
465         &                xthresh2, xkgraz2, epsher2, epsher2min, sigma2, unass2, grazflux, ln_dvm_meso,  &
466         &                xfracmig
467      !!----------------------------------------------------------------------
468      !
469      IF(lwp) THEN
470         WRITE(numout,*) 
471         WRITE(numout,*) 'p4z_meso_init : Initialization of mesozooplankton parameters'
472         WRITE(numout,*) '~~~~~~~~~~~~~'
473      ENDIF
474      !
475      REWIND( numnatp_ref )              ! Namelist namp4zmes in reference namelist : Pisces mesozooplankton
476      READ  ( numnatp_ref, namp4zmes, IOSTAT = ios, ERR = 901)
477901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zmes in reference namelist' )
478      REWIND( numnatp_cfg )              ! Namelist namp4zmes in configuration namelist : Pisces mesozooplankton
479      READ  ( numnatp_cfg, namp4zmes, IOSTAT = ios, ERR = 902 )
480902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zmes in configuration namelist' )
481      IF(lwm) WRITE( numonp, namp4zmes )
482      !
483      IF(lwp) THEN                         ! control print
484         WRITE(numout,*) '   Namelist : namp4zmes'
485         WRITE(numout,*) '      part of calcite not dissolved in mesozoo guts  part2        =', part2
486         WRITE(numout,*) '      mesozoo preference for phyto                   xpref2n      =', xpref2n
487         WRITE(numout,*) '      mesozoo preference for diatoms                 xpref2d      =', xpref2d
488         WRITE(numout,*) '      mesozoo preference for zoo                     xpref2z      =', xpref2z
489         WRITE(numout,*) '      mesozoo preference for poc                     xpref2c      =', xpref2c
490         WRITE(numout,*) '      microzoo feeding threshold  for mesozoo        xthresh2zoo  =', xthresh2zoo
491         WRITE(numout,*) '      diatoms feeding threshold  for mesozoo         xthresh2dia  =', xthresh2dia
492         WRITE(numout,*) '      nanophyto feeding threshold for mesozoo        xthresh2phy  =', xthresh2phy
493         WRITE(numout,*) '      poc feeding threshold for mesozoo              xthresh2poc  =', xthresh2poc
494         WRITE(numout,*) '      feeding threshold for mesozooplankton          xthresh2     =', xthresh2
495         WRITE(numout,*) '      exsudation rate of mesozooplankton             resrat2      =', resrat2
496         WRITE(numout,*) '      mesozooplankton mortality rate                 mzrat2       =', mzrat2
497         WRITE(numout,*) '      maximal mesozoo grazing rate                   grazrat2     =', grazrat2
498         WRITE(numout,*) '      mesozoo flux feeding rate                      grazflux     =', grazflux
499         WRITE(numout,*) '      non assimilated fraction of P by mesozoo       unass2       =', unass2
500         WRITE(numout,*) '      Efficiency of Mesozoo growth                   epsher2      =', epsher2
501         WRITE(numout,*) '      Minimum Efficiency of Mesozoo growth           epsher2min   =', epsher2min
502         WRITE(numout,*) '      Fraction of mesozoo excretion as DOM           sigma2       =', sigma2
503         WRITE(numout,*) '      half sturation constant for grazing 2          xkgraz2      =', xkgraz2
504         WRITE(numout,*) '      Diurnal vertical migration of mesozoo.         ln_dvm_meso  =', ln_dvm_meso
505         WRITE(numout,*) '      Fractional biomass of meso  that performs DVM  xfracmig     =', xfracmig
506      ENDIF
507      !
508   END SUBROUTINE p4z_meso_init
509
510   SUBROUTINE p4z_meso_depmig 
511      !!----------------------------------------------------------------------
512      !!                  ***  ROUTINE p4z_meso_depmig  ***
513      !!
514      !! ** Purpose :   Computation the migration depth of mesozooplankton
515      !!
516      !! ** Method  :   Computes the DVM depth of mesozooplankton from oxygen
517      !!      temperature and chlorophylle following the parameterization
518      !!      proposed by Bianchi et al. (2013)
519      !!----------------------------------------------------------------------
520      INTEGER  :: ji, jj, jk
521      !
522      REAL(wp) :: totchl
523      REAL(wp), DIMENSION(jpi,jpj) :: oxymoy, tempmoy, zdepmoy
524
525      !!---------------------------------------------------------------------
526      !
527      IF( ln_timing == 1 )  CALL timing_start('p4z_meso_zdepmig')
528      !
529      oxymoy(:,:)  = 0.
530      tempmoy(:,:) = 0.
531      zdepmoy(:,:) = 0.
532      depmig (:,:) = 5.
533      kmig   (:,:) = 1
534      !
535      ! Compute the averaged values of oxygen, temperature over the domain
536      ! 150m to 500 m depth.
537      ! ------------------------------------------------------------------
538      DO jk =1, jpk
539         DO jj = 1, jpj
540            DO ji = 1, jpi
541               IF (tmask(ji,jj,jk) == 1.) THEN
542                  IF (gdept_n(ji,jj,jk) >= 150. .AND. gdept_n(ji,jj,jk) <= 500.) THEN
543                     oxymoy(ji,jj) = oxymoy(ji,jj) + trb(ji,jj,jk,jpoxy)*e3t_n(ji,jj,jk)*1E6
544                     tempmoy(ji,jj) = tempmoy(ji,jj) + tsn(ji,jj,jk,jp_tem)*e3t_n(ji,jj,jk)
545                     zdepmoy(ji,jj) = zdepmoy(ji,jj) + e3t_n(ji,jj,jk)
546                  ENDIF
547               ENDIF
548            END DO
549         END DO
550      END DO
551
552      ! Compute the difference between surface values and the mean values in the mesopelagic
553      ! domain
554      ! ------------------------------------------------------------------------------------
555      DO jj = 1, jpj
556         DO ji = 1, jpi
557            oxymoy(ji,jj) = trb(ji,jj,1,jpoxy)*1E6 - oxymoy(ji,jj) / (zdepmoy(ji,jj) + rtrn)
558            tempmoy(ji,jj) = tsn(ji,jj,1,jp_tem)-tempmoy(ji,jj) / (zdepmoy(ji,jj) + rtrn)
559         END DO
560      END DO
561      !
562      ! Computation of the migration depth based on the parameterization of
563      ! Bianchi et al. (2013)
564      ! -------------------------------------------------------------------
565      DO jj = 1, jpj
566         DO ji = 1, jpi
567            IF (tmask(ji,jj,1) == 1.) THEN
568               totchl = (trb(ji,jj,1,jpnch)+trb(ji,jj,1,jpdch))*1E6
569               depmig(ji,jj) = 398. - 0.56 * oxymoy(ji,jj) -115. * log10(totchl) + 0.36 * hmld(ji,jj) -2.4 * tempmoy(ji,jj)
570            ENDIF
571         END DO
572      END DO
573      !
574      ! Computation of the corresponding jk indice
575      ! ------------------------------------------
576      DO jk = 1, jpk-1
577         DO jj = 1, jpj
578            DO ji = 1, jpi
579               IF (depmig(ji,jj) .GE. gdepw_n(ji,jj,jk) .AND. depmig(ji,jj) .LT. gdepw_n(ji,jj,jk+1) ) THEN
580                  kmig(ji,jj) = jk
581               ENDIF
582            END DO
583         END DO
584      END DO
585      !
586      ! Correction of the migration depth and indice based on O2 levels
587      ! If O2 is too low, imposing a migration depth at this low O2 levels
588      ! would lead to negative O2 concentrations (respiration while O2 is close
589      ! to 0. Thus, to avoid that problem, the migration depth is adjusted so
590      ! that it falls above the OMZ
591      ! -----------------------------------------------------------------------
592      DO ji =1, jpi
593         DO jj = 1, jpj
594            IF (trb(ji,jj,kmig(ji,jj),jpoxy) < 5E-6) THEN
595               DO jk = kmig(ji,jj),1,-1
596                  IF (trb(ji,jj,jk,jpoxy) >= 5E-6 .AND. trb(ji,jj,jk+1,jpoxy)  < 5E-6) THEN
597                     kmig(ji,jj) = jk
598                     depmig(ji,jj) = gdept_n(ji,jj,jk)
599                  ENDIF
600               END DO
601            ENDIF
602         END DO
603      END DO
604      !
605      IF( ln_timing )   CALL timing_stop('p4z_meso_depmig')
606      !
607   END SUBROUTINE p4z_meso_depmig
608
609   INTEGER FUNCTION p4z_meso_alloc()
610      !!----------------------------------------------------------------------
611      !!                     ***  ROUTINE p4z_meso_alloc  ***
612      !!----------------------------------------------------------------------
613      !
614      ALLOCATE( depmig(jpi,jpj), kmig(jpi,jpj), STAT= p4z_meso_alloc  )
615      !
616      IF( p4z_meso_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_meso_alloc : failed to allocate arrays.' )
617      !
618   END FUNCTION p4z_meso_alloc
619
620   !!======================================================================
621END MODULE p4zmeso
Note: See TracBrowser for help on using the repository browser.