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 @ 13234

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

slight change in the namelist PISCES

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