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

Last change on this file since 14276 was 14276, checked in by aumont, 3 years ago

numerous updates to PISCES, PISCES-QUOTA and the sediment module

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