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.
p4zmort.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/p4zmort.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: 12.6 KB
Line 
1MODULE p4zmort
2   !!======================================================================
3   !!                         ***  MODULE p4zmort  ***
4   !! TOP :   PISCES Compute the mortality terms for phytoplankton
5   !!======================================================================
6   !! History :   1.0  !  2002     (O. Aumont)  Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!----------------------------------------------------------------------
9   !!   p4z_mort       : Compute the mortality terms for phytoplankton
10   !!   p4z_mort_init  : Initialize the mortality params for phytoplankton
11   !!----------------------------------------------------------------------
12   USE oce_trc         ! shared variables between ocean and passive tracers
13   USE trc             ! passive tracers common variables
14   USE sms_pisces      ! PISCES Source Minus Sink variables
15   USE p4zprod         ! Primary productivity
16   USE p4zlim          ! Phytoplankton limitation terms
17   USE prtctl_trc      ! print control for debugging
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   p4z_mort           ! Called from p4zbio.F90
23   PUBLIC   p4z_mort_init      ! Called from trcini_pisces.F90
24
25   REAL(wp), PUBLIC ::   wchln    !: Quadratic mortality rate of nanophytoplankton
26   REAL(wp), PUBLIC ::   wchld    !: Quadratic mortality rate of diatoms
27   REAL(wp), PUBLIC ::   wchldm   !: Maximum quadratic mortality rate of diatoms
28   REAL(wp), PUBLIC ::   mpratn   !: Linear mortality rate of nanophytoplankton
29   REAL(wp), PUBLIC ::   mpratd   !: Linear mortality rate of diatoms
30
31   !!----------------------------------------------------------------------
32   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
33   !! $Id$
34   !! Software governed by the CeCILL license (see ./LICENSE)
35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE p4z_mort( kt )
39      !!---------------------------------------------------------------------
40      !!                     ***  ROUTINE p4z_mort  ***
41      !!
42      !! ** Purpose :   Calls the different subroutine to compute
43      !!                the different phytoplankton mortality terms
44      !!
45      !! ** Method  : - ???
46      !!---------------------------------------------------------------------
47      INTEGER, INTENT(in) ::   kt ! ocean time step
48      !!---------------------------------------------------------------------
49      !
50      CALL p4z_mort_nano            ! nanophytoplankton
51      CALL p4z_mort_diat            ! diatoms
52      !
53   END SUBROUTINE p4z_mort
54
55
56   SUBROUTINE p4z_mort_nano
57      !!---------------------------------------------------------------------
58      !!                     ***  ROUTINE p4z_mort_nano  ***
59      !!
60      !! ** Purpose :   Compute the mortality terms for nanophytoplankton
61      !!
62      !! ** Method  :   Both quadratic and simili linear mortality terms
63      !!---------------------------------------------------------------------
64      INTEGER  ::   ji, jj, jk
65      REAL(wp) ::   zsizerat, zcompaph
66      REAL(wp) ::   zfactfe, zfactch, zprcaca, zfracal
67      REAL(wp) ::   ztortp , zrespp , zmortp 
68      CHARACTER (len=25) ::   charout
69      !!---------------------------------------------------------------------
70      !
71      IF( ln_timing )   CALL timing_start('p4z_mort_nano')
72      !
73      prodcal(:,:,:) = 0._wp   ! calcite production variable set to zero
74      DO jk = 1, jpkm1
75         DO jj = 1, jpj
76            DO ji = 1, jpi
77               zcompaph = MAX( ( trb(ji,jj,jk,jpphy) - 1e-8 ), 0.e0 )
78               !     When highly limited by macronutrients, very small cells
79               !     dominate the community. As a consequence, aggregation
80               !     due to turbulence is negligible. Mortality is also set
81               !     to 0
82               zsizerat = MIN(1., MAX( 0., (quotan(ji,jj,jk) - 0.2) / 0.3) ) * trb(ji,jj,jk,jpphy)
83
84               ! Quadratic mortality of nano due to aggregation during
85               ! blooms (Doney et al. 1996)
86               ! -----------------------------------------------------
87               zrespp = wchln * 1.e6 * xstep * xdiss(ji,jj,jk) * zcompaph * zsizerat 
88
89               ! Phytoplankton linear mortality
90               ! A michaelis-menten like term is introduced to avoid
91               ! extinction of nanophyto in highly limited areas
92               ! ----------------------------------------------------
93               ztortp = mpratn * xstep * zcompaph / ( xkmort + trb(ji,jj,jk,jpphy) ) * zsizerat
94
95               zmortp = zrespp + ztortp
96
97               ! Update the arrays TRA which contains the biological sources and sinks
98               zfactfe = trb(ji,jj,jk,jpnfe)/(trb(ji,jj,jk,jpphy)+rtrn)
99               zfactch = trb(ji,jj,jk,jpnch)/(trb(ji,jj,jk,jpphy)+rtrn)
100               tra(ji,jj,jk,jpphy) = tra(ji,jj,jk,jpphy) - zmortp
101               tra(ji,jj,jk,jpnch) = tra(ji,jj,jk,jpnch) - zmortp * zfactch
102               tra(ji,jj,jk,jpnfe) = tra(ji,jj,jk,jpnfe) - zmortp * zfactfe
103
104               ! Production PIC particles due to mortality
105               zprcaca = xfracal(ji,jj,jk) * zmortp
106               prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo)
107
108               ! POC associated with the shell is supposed to be routed to
109               ! big particles because of the ballasting effect
110               zfracal = 0.5 * xfracal(ji,jj,jk)
111               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) - zprcaca
112               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2. * zprcaca
113               tra(ji,jj,jk,jpcal) = tra(ji,jj,jk,jpcal) + zprcaca
114               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zfracal * zmortp
115               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + ( 1. - zfracal ) * zmortp
116               prodpoc(ji,jj,jk) = prodpoc(ji,jj,jk) + ( 1. - zfracal ) * zmortp
117               prodgoc(ji,jj,jk) = prodgoc(ji,jj,jk) + zfracal * zmortp
118
119               ! Update the arrays TRA which contains the biological sources and sinks
120               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + ( 1. - zfracal ) * zmortp * zfactfe
121               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zfracal * zmortp * zfactfe
122            END DO
123         END DO
124      END DO
125      !
126       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
127         WRITE(charout, FMT="('nano')")
128         CALL prt_ctl_trc_info(charout)
129         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
130       ENDIF
131      !
132      IF( ln_timing )   CALL timing_stop('p4z_mort_nano')
133      !
134   END SUBROUTINE p4z_mort_nano
135
136
137   SUBROUTINE p4z_mort_diat
138      !!---------------------------------------------------------------------
139      !!                     ***  ROUTINE p4z_mort_diat  ***
140      !!
141      !! ** Purpose :   Compute the mortality terms for diatoms
142      !!
143      !! ** Method  : - Both quadratic and simili linear mortality terms
144      !!---------------------------------------------------------------------
145      INTEGER  ::   ji, jj, jk
146      REAL(wp) ::   zfactfe,zfactsi,zfactch, zcompadi
147      REAL(wp) ::   zrespp2, ztortp2, zmortp2
148      REAL(wp) ::   zlim2, zlim1
149      CHARACTER (len=25) ::   charout
150      !!---------------------------------------------------------------------
151      !
152      IF( ln_timing )   CALL timing_start('p4z_mort_diat')
153      !
154      ! Aggregation term for diatoms is increased in case of nutrient
155      ! stress as observed in reality. The stressed cells become more
156      ! sticky and coagulate to sink quickly out of the euphotic zone
157      ! This is due to the production of EPS by stressed cells
158      ! -------------------------------------------------------------
159
160      DO jk = 1, jpkm1
161         DO jj = 1, jpj
162            DO ji = 1, jpi
163
164               zcompadi = MAX( ( trb(ji,jj,jk,jpdia) - 1e-9), 0. )
165
166               ! Aggregation term for diatoms is increased in case of nutrient
167               ! stress as observed in reality. The stressed cells become more
168               ! sticky and coagulate to sink quickly out of the euphotic zone
169               ! ------------------------------------------------------------
170               zlim2   = xlimdia(ji,jj,jk) * xlimdia(ji,jj,jk)
171               zlim1   = 0.25 * ( 1. - zlim2 ) / ( 0.25 + zlim2 ) 
172               zrespp2 = 1.e6 * xstep * (  wchld + wchldm * zlim1 ) * xdiss(ji,jj,jk) * zcompadi * trb(ji,jj,jk,jpdia)
173
174               ! Phytoplankton linear mortality
175               ! A michaelis-menten like term is introduced to avoid
176               ! extinction of diatoms in highly limited areas
177               !  ---------------------------------------------------
178               ztortp2 = mpratd * xstep * trb(ji,jj,jk,jpdia)  / ( xkmort + trb(ji,jj,jk,jpdia) ) * zcompadi 
179
180               zmortp2 = zrespp2 + ztortp2
181
182               ! Update the arrays tra which contains the biological sources and sinks
183               !   ---------------------------------------------------------------------
184               zfactch = trb(ji,jj,jk,jpdch) / ( trb(ji,jj,jk,jpdia) + rtrn )
185               zfactfe = trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) + rtrn )
186               zfactsi = trb(ji,jj,jk,jpdsi) / ( trb(ji,jj,jk,jpdia) + rtrn )
187               tra(ji,jj,jk,jpdia) = tra(ji,jj,jk,jpdia) - zmortp2 
188               tra(ji,jj,jk,jpdch) = tra(ji,jj,jk,jpdch) - zmortp2 * zfactch
189               tra(ji,jj,jk,jpdfe) = tra(ji,jj,jk,jpdfe) - zmortp2 * zfactfe
190               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zmortp2 * zfactsi
191               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) + zmortp2 * zfactsi
192
193               ! Half of the linear mortality term is routed to big particles
194               ! becaue of the ballasting effect
195               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zrespp2 + 0.5 * ztortp2
196               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + 0.5 * ztortp2
197               prodpoc(ji,jj,jk) = prodpoc(ji,jj,jk) + 0.5 * ztortp2
198               prodgoc(ji,jj,jk) = prodgoc(ji,jj,jk) + zrespp2 + 0.5 * ztortp2
199               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + 0.5 * ztortp2 * zfactfe
200               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + ( zrespp2 + 0.5 * ztortp2 ) * zfactfe
201            END DO
202         END DO
203      END DO
204      !
205      IF(ln_ctl) THEN      ! print mean trends (used for debugging)
206         WRITE(charout, FMT="('diat')")
207         CALL prt_ctl_trc_info(charout)
208         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
209      ENDIF
210      !
211      IF( ln_timing )   CALL timing_stop('p4z_mort_diat')
212      !
213   END SUBROUTINE p4z_mort_diat
214
215
216   SUBROUTINE p4z_mort_init
217      !!----------------------------------------------------------------------
218      !!                  ***  ROUTINE p4z_mort_init  ***
219      !!
220      !! ** Purpose :   Initialization of phytoplankton parameters
221      !!
222      !! ** Method  :   Read the namp4zmort namelist and check the parameters
223      !!              called at the first timestep
224      !!
225      !! ** input   :   Namelist namp4zmort
226      !!
227      !!----------------------------------------------------------------------
228      INTEGER ::   ios   ! Local integer
229      !
230      NAMELIST/namp4zmort/ wchln, wchld, wchldm, mpratn, mpratd
231      !!----------------------------------------------------------------------
232      !
233      IF(lwp) THEN
234         WRITE(numout,*) 
235         WRITE(numout,*) 'p4z_mort_init : Initialization of phytoplankton mortality parameters'
236         WRITE(numout,*) '~~~~~~~~~~~~~'
237      ENDIF
238      !
239      REWIND( numnatp_ref )              ! Namelist namp4zmort in reference namelist : Pisces phytoplankton
240      READ  ( numnatp_ref, namp4zmort, IOSTAT = ios, ERR = 901)
241901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zmort in reference namelist' )
242      REWIND( numnatp_cfg )              ! Namelist namp4zmort in configuration namelist : Pisces phytoplankton
243      READ  ( numnatp_cfg, namp4zmort, IOSTAT = ios, ERR = 902 )
244902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zmort in configuration namelist' )
245      IF(lwm) WRITE( numonp, namp4zmort )
246      !
247      IF(lwp) THEN                         ! control print
248         WRITE(numout,*) '   Namelist : namp4zmort'
249         WRITE(numout,*) '      quadratic mortality of phytoplankton        wchln  =', wchln
250         WRITE(numout,*) '      maximum quadratic mortality of diatoms      wchld  =', wchld
251         WRITE(numout,*) '      maximum quadratic mortality of diatoms      wchldm =', wchldm
252         WRITE(numout,*) '      phytoplankton mortality rate                mpratn =', mpratn
253         WRITE(numout,*) '      Diatoms mortality rate                      mpratd =', mpratd
254      ENDIF
255      !
256   END SUBROUTINE p4z_mort_init
257
258   !!======================================================================
259END MODULE p4zmort
Note: See TracBrowser for help on using the repository browser.