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 branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/2015/dev_r5803_NOC_WAD/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmort.F90 @ 5870

Last change on this file since 5870 was 5870, checked in by acc, 8 years ago

Branch 2015/dev_r5803_NOC_WAD. Merge in trunk changes from 5803 to 5869 in preparation for merge. Also tidied and reorganised some wetting and drying code. Renamed wadlmt.F90 to wetdry.F90. Wetting drying code changes restricted to domzgr.F90, domvvl.F90 nemogcm.F90 sshwzv.F90, dynspg_ts.F90, wetdry.F90 and dynhpg.F90. Code passes full SETTE tests with ln_wd=.false.. Still awaiting test case for checking with ln_wd=.false.

  • 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#if defined key_pisces
10   !!----------------------------------------------------------------------
11   !!   'key_pisces'                                       PISCES bio-model
12   !!----------------------------------------------------------------------
13   !!   p4z_mort       :   Compute the mortality terms for phytoplankton
14   !!   p4z_mort_init  :   Initialize the mortality params for phytoplankton
15   !!----------------------------------------------------------------------
16   USE oce_trc         !  shared variables between ocean and passive tracers
17   USE trc             !  passive tracers common variables
18   USE sms_pisces      !  PISCES Source Minus Sink variables
19   USE p4zsink         !  vertical flux of particulate matter due to sinking
20   USE p4zprod         !  Primary productivity
21   USE prtctl_trc      !  print control for debugging
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   p4z_mort   
27   PUBLIC   p4z_mort_init   
28
29   !! * Shared module variables
30   REAL(wp), PUBLIC :: wchl    !:
31   REAL(wp), PUBLIC :: wchld   !:
32   REAL(wp), PUBLIC :: wchldm  !:
33   REAL(wp), PUBLIC :: mprat   !:
34   REAL(wp), PUBLIC :: mprat2  !:
35
36
37   !!----------------------------------------------------------------------
38   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
39   !! $Id$
40   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE p4z_mort( kt )
46      !!---------------------------------------------------------------------
47      !!                     ***  ROUTINE p4z_mort  ***
48      !!
49      !! ** Purpose :   Calls the different subroutine to initialize and compute
50      !!                the different phytoplankton mortality terms
51      !!
52      !! ** Method  : - ???
53      !!---------------------------------------------------------------------
54      INTEGER, INTENT(in) ::   kt ! ocean time step
55      !!---------------------------------------------------------------------
56
57      CALL p4z_nano            ! nanophytoplankton
58
59      CALL p4z_diat            ! diatoms
60
61   END SUBROUTINE p4z_mort
62
63
64   SUBROUTINE p4z_nano
65      !!---------------------------------------------------------------------
66      !!                     ***  ROUTINE p4z_nano  ***
67      !!
68      !! ** Purpose :   Compute the mortality terms for nanophytoplankton
69      !!
70      !! ** Method  : - ???
71      !!---------------------------------------------------------------------
72      INTEGER  :: ji, jj, jk
73      REAL(wp) :: zsizerat, zcompaph
74      REAL(wp) :: zfactfe, zfactch, zprcaca, zfracal
75      REAL(wp) :: ztortp , zrespp , zmortp , zstep
76      CHARACTER (len=25) :: charout
77      !!---------------------------------------------------------------------
78      !
79      IF( nn_timing == 1 )  CALL timing_start('p4z_nano')
80      !
81      prodcal(:,:,:) = 0.  !: calcite production variable set to zero
82      DO jk = 1, jpkm1
83         DO jj = 1, jpj
84            DO ji = 1, jpi
85               zcompaph = MAX( ( trb(ji,jj,jk,jpphy) - 1e-8 ), 0.e0 )
86               zstep    = xstep
87# if defined key_degrad
88               zstep    = zstep * facvol(ji,jj,jk)
89# endif
90               !     When highly limited by macronutrients, very small cells
91               !     dominate the community. As a consequence, aggregation
92               !     due to turbulence is negligible. Mortality is also set
93               !     to 0
94               zsizerat = MIN(1., MAX( 0., (quotan(ji,jj,jk) - 0.2) / 0.3) ) * trb(ji,jj,jk,jpphy)
95               !     Squared mortality of Phyto similar to a sedimentation term during
96               !     blooms (Doney et al. 1996)
97               zrespp = wchl * 1.e6 * zstep * xdiss(ji,jj,jk) * zcompaph * zsizerat 
98
99               !     Phytoplankton mortality. This mortality loss is slightly
100               !     increased when nutrients are limiting phytoplankton growth
101               !     as observed for instance in case of iron limitation.
102               ztortp = mprat * xstep * zcompaph / ( xkmort + trb(ji,jj,jk,jpphy) ) * zsizerat
103
104               zmortp = zrespp + ztortp
105
106               !   Update the arrays TRA which contains the biological sources and sinks
107
108               zfactfe = trb(ji,jj,jk,jpnfe)/(trb(ji,jj,jk,jpphy)+rtrn)
109               zfactch = trb(ji,jj,jk,jpnch)/(trb(ji,jj,jk,jpphy)+rtrn)
110               tra(ji,jj,jk,jpphy) = tra(ji,jj,jk,jpphy) - zmortp
111               tra(ji,jj,jk,jpnch) = tra(ji,jj,jk,jpnch) - zmortp * zfactch
112               tra(ji,jj,jk,jpnfe) = tra(ji,jj,jk,jpnfe) - zmortp * zfactfe
113               zprcaca = xfracal(ji,jj,jk) * zmortp
114               !
115               prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo)
116               !
117               zfracal = 0.5 * xfracal(ji,jj,jk)
118               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) - zprcaca
119               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2. * zprcaca
120               tra(ji,jj,jk,jpcal) = tra(ji,jj,jk,jpcal) + zprcaca
121#if defined key_kriest
122               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + zmortp
123               tra(ji,jj,jk,jpnum) = tra(ji,jj,jk,jpnum) + ztortp * xkr_dnano + zrespp * xkr_ddiat
124               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zmortp * zfactfe
125#else
126               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zfracal * zmortp
127               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + ( 1. - zfracal ) * zmortp
128               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + ( 1. - zfracal ) * zmortp * zfactfe
129               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zfracal * zmortp * zfactfe
130#endif
131            END DO
132         END DO
133      END DO
134      !
135       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
136         WRITE(charout, FMT="('nano')")
137         CALL prt_ctl_trc_info(charout)
138         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
139       ENDIF
140      !
141      IF( nn_timing == 1 )  CALL timing_stop('p4z_nano')
142      !
143   END SUBROUTINE p4z_nano
144
145   SUBROUTINE p4z_diat
146      !!---------------------------------------------------------------------
147      !!                     ***  ROUTINE p4z_diat  ***
148      !!
149      !! ** Purpose :   Compute the mortality terms for diatoms
150      !!
151      !! ** Method  : - ???
152      !!---------------------------------------------------------------------
153      INTEGER  ::  ji, jj, jk
154      REAL(wp) ::  zfactfe,zfactsi,zfactch, zcompadi
155      REAL(wp) ::  zrespp2, ztortp2, zmortp2, zstep
156      REAL(wp) ::  zlim2, zlim1
157      CHARACTER (len=25) :: charout
158      !!---------------------------------------------------------------------
159      !
160      IF( nn_timing == 1 )  CALL timing_start('p4z_diat')
161      !
162
163      !    Aggregation term for diatoms is increased in case of nutrient
164      !    stress as observed in reality. The stressed cells become more
165      !    sticky and coagulate to sink quickly out of the euphotic zone
166      !     ------------------------------------------------------------
167
168      DO jk = 1, jpkm1
169         DO jj = 1, jpj
170            DO ji = 1, jpi
171
172               zcompadi = MAX( ( trb(ji,jj,jk,jpdia) - 1e-9), 0. )
173
174               !    Aggregation term for diatoms is increased in case of nutrient
175               !    stress as observed in reality. The stressed cells become more
176               !    sticky and coagulate to sink quickly out of the euphotic zone
177               !     ------------------------------------------------------------
178               zstep   = xstep
179# if defined key_degrad
180               zstep = zstep * facvol(ji,jj,jk)
181# endif
182               !  Phytoplankton respiration
183               !     ------------------------
184               zlim2   = xlimdia(ji,jj,jk) * xlimdia(ji,jj,jk)
185               zlim1   = 0.25 * ( 1. - zlim2 ) / ( 0.25 + zlim2 ) 
186               zrespp2 = 1.e6 * zstep * (  wchld + wchldm * zlim1 ) * xdiss(ji,jj,jk) * zcompadi * trb(ji,jj,jk,jpdia)
187
188               !     Phytoplankton mortality.
189               !     ------------------------
190               ztortp2 = mprat2 * zstep * trb(ji,jj,jk,jpdia)  / ( xkmort + trb(ji,jj,jk,jpdia) ) * zcompadi 
191
192               zmortp2 = zrespp2 + ztortp2
193
194               !   Update the arrays tra which contains the biological sources and sinks
195               !   ---------------------------------------------------------------------
196               zfactch = trb(ji,jj,jk,jpdch) / ( trb(ji,jj,jk,jpdia) + rtrn )
197               zfactfe = trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) + rtrn )
198               zfactsi = trb(ji,jj,jk,jpdsi) / ( trb(ji,jj,jk,jpdia) + rtrn )
199               tra(ji,jj,jk,jpdia) = tra(ji,jj,jk,jpdia) - zmortp2 
200               tra(ji,jj,jk,jpdch) = tra(ji,jj,jk,jpdch) - zmortp2 * zfactch
201               tra(ji,jj,jk,jpdfe) = tra(ji,jj,jk,jpdfe) - zmortp2 * zfactfe
202               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zmortp2 * zfactsi
203               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) + zmortp2 * zfactsi
204#if defined key_kriest
205               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + zmortp2 
206               tra(ji,jj,jk,jpnum) = tra(ji,jj,jk,jpnum) + ztortp2 * xkr_ddiat + zrespp2 * xkr_daggr
207               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zmortp2 * zfactfe
208#else
209               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zrespp2 + 0.5 * ztortp2
210               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + 0.5 * ztortp2
211               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + 0.5 * ztortp2 * zfactfe
212               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + ( zrespp2 + 0.5 * ztortp2 ) * zfactfe
213#endif
214            END DO
215         END DO
216      END DO
217      !
218      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
219         WRITE(charout, FMT="('diat')")
220         CALL prt_ctl_trc_info(charout)
221         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
222      ENDIF
223      !
224      IF( nn_timing == 1 )  CALL timing_stop('p4z_diat')
225      !
226   END SUBROUTINE p4z_diat
227
228   SUBROUTINE p4z_mort_init
229
230      !!----------------------------------------------------------------------
231      !!                  ***  ROUTINE p4z_mort_init  ***
232      !!
233      !! ** Purpose :   Initialization of phytoplankton parameters
234      !!
235      !! ** Method  :   Read the nampismort namelist and check the parameters
236      !!      called at the first timestep
237      !!
238      !! ** input   :   Namelist nampismort
239      !!
240      !!----------------------------------------------------------------------
241
242      NAMELIST/nampismort/ wchl, wchld, wchldm, mprat, mprat2
243      INTEGER :: ios                 ! Local integer output status for namelist read
244
245      REWIND( numnatp_ref )              ! Namelist nampismort in reference namelist : Pisces phytoplankton
246      READ  ( numnatp_ref, nampismort, IOSTAT = ios, ERR = 901)
247901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismort in reference namelist', lwp )
248
249      REWIND( numnatp_cfg )              ! Namelist nampismort in configuration namelist : Pisces phytoplankton
250      READ  ( numnatp_cfg, nampismort, IOSTAT = ios, ERR = 902 )
251902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismort in configuration namelist', lwp )
252      IF(lwm) WRITE ( numonp, nampismort )
253
254      IF(lwp) THEN                         ! control print
255         WRITE(numout,*) ' '
256         WRITE(numout,*) ' Namelist parameters for phytoplankton mortality, nampismort'
257         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
258         WRITE(numout,*) '    quadratic mortality of phytoplankton      wchl      =', wchl
259         WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchld     =', wchld
260         WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchldm    =', wchldm
261         WRITE(numout,*) '    phytoplankton mortality rate              mprat     =', mprat
262         WRITE(numout,*) '    Diatoms mortality rate                    mprat2    =', mprat2
263      ENDIF
264
265   END SUBROUTINE p4z_mort_init
266
267#else
268   !!======================================================================
269   !!  Dummy module :                                   No PISCES bio-model
270   !!======================================================================
271CONTAINS
272   SUBROUTINE p4z_mort                    ! Empty routine
273   END SUBROUTINE p4z_mort
274#endif 
275
276   !!======================================================================
277END MODULE p4zmort
Note: See TracBrowser for help on using the repository browser.