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/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmort.F90 @ 7041

Last change on this file since 7041 was 7041, checked in by cetlod, 7 years ago

ROBUST5_CNRS : implementation of part I of new TOP interface - 1st step -, see ticket #1782

  • Property svn:keywords set to Id
File size: 11.8 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
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               !     When highly limited by macronutrients, very small cells
87               !     dominate the community. As a consequence, aggregation
88               !     due to turbulence is negligible. Mortality is also set
89               !     to 0
90               zsizerat = MIN(1., MAX( 0., (quotan(ji,jj,jk) - 0.2) / 0.3) ) * trb(ji,jj,jk,jpphy)
91               !     Squared mortality of Phyto similar to a sedimentation term during
92               !     blooms (Doney et al. 1996)
93               zrespp = wchl * 1.e6 * xstep * xdiss(ji,jj,jk) * zcompaph * zsizerat 
94
95               !     Phytoplankton mortality. This mortality loss is slightly
96               !     increased when nutrients are limiting phytoplankton growth
97               !     as observed for instance in case of iron limitation.
98               ztortp = mprat * xstep * zcompaph / ( xkmort + trb(ji,jj,jk,jpphy) ) * zsizerat
99
100               zmortp = zrespp + ztortp
101
102               !   Update the arrays TRA which contains the biological sources and sinks
103
104               zfactfe = trb(ji,jj,jk,jpnfe)/(trb(ji,jj,jk,jpphy)+rtrn)
105               zfactch = trb(ji,jj,jk,jpnch)/(trb(ji,jj,jk,jpphy)+rtrn)
106               tra(ji,jj,jk,jpphy) = tra(ji,jj,jk,jpphy) - zmortp
107               tra(ji,jj,jk,jpnch) = tra(ji,jj,jk,jpnch) - zmortp * zfactch
108               tra(ji,jj,jk,jpnfe) = tra(ji,jj,jk,jpnfe) - zmortp * zfactfe
109               zprcaca = xfracal(ji,jj,jk) * zmortp
110               !
111               prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo)
112               !
113               zfracal = 0.5 * xfracal(ji,jj,jk)
114               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) - zprcaca
115               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2. * zprcaca
116               tra(ji,jj,jk,jpcal) = tra(ji,jj,jk,jpcal) + zprcaca
117               tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) + zfracal * zmortp
118               tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + ( 1. - zfracal ) * zmortp
119               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + ( 1. - zfracal ) * zmortp * zfactfe
120               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zfracal * zmortp * zfactfe
121            END DO
122         END DO
123      END DO
124      !
125       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
126         WRITE(charout, FMT="('nano')")
127         CALL prt_ctl_trc_info(charout)
128         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
129       ENDIF
130      !
131      IF( nn_timing == 1 )  CALL timing_stop('p4z_nano')
132      !
133   END SUBROUTINE p4z_nano
134
135   SUBROUTINE p4z_diat
136      !!---------------------------------------------------------------------
137      !!                     ***  ROUTINE p4z_diat  ***
138      !!
139      !! ** Purpose :   Compute the mortality terms for diatoms
140      !!
141      !! ** Method  : - ???
142      !!---------------------------------------------------------------------
143      INTEGER  ::  ji, jj, jk
144      REAL(wp) ::  zfactfe,zfactsi,zfactch, zcompadi
145      REAL(wp) ::  zrespp2, ztortp2, zmortp2
146      REAL(wp) ::  zlim2, zlim1
147      CHARACTER (len=25) :: charout
148      !!---------------------------------------------------------------------
149      !
150      IF( nn_timing == 1 )  CALL timing_start('p4z_diat')
151      !
152
153      !    Aggregation term for diatoms is increased in case of nutrient
154      !    stress as observed in reality. The stressed cells become more
155      !    sticky and coagulate to sink quickly out of the euphotic zone
156      !     ------------------------------------------------------------
157
158      DO jk = 1, jpkm1
159         DO jj = 1, jpj
160            DO ji = 1, jpi
161
162               zcompadi = MAX( ( trb(ji,jj,jk,jpdia) - 1e-9), 0. )
163
164               !    Aggregation term for diatoms is increased in case of nutrient
165               !    stress as observed in reality. The stressed cells become more
166               !    sticky and coagulate to sink quickly out of the euphotic zone
167               !     ------------------------------------------------------------
168               !  Phytoplankton respiration
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 mortality.
175               !     ------------------------
176               ztortp2 = mprat2 * xstep * trb(ji,jj,jk,jpdia)  / ( xkmort + trb(ji,jj,jk,jpdia) ) * zcompadi 
177
178               zmortp2 = zrespp2 + ztortp2
179
180               !   Update the arrays tra which contains the biological sources and sinks
181               !   ---------------------------------------------------------------------
182               zfactch = trb(ji,jj,jk,jpdch) / ( trb(ji,jj,jk,jpdia) + rtrn )
183               zfactfe = trb(ji,jj,jk,jpdfe) / ( trb(ji,jj,jk,jpdia) + rtrn )
184               zfactsi = trb(ji,jj,jk,jpdsi) / ( trb(ji,jj,jk,jpdia) + rtrn )
185               tra(ji,jj,jk,jpdia) = tra(ji,jj,jk,jpdia) - zmortp2 
186               tra(ji,jj,jk,jpdch) = tra(ji,jj,jk,jpdch) - zmortp2 * zfactch
187               tra(ji,jj,jk,jpdfe) = tra(ji,jj,jk,jpdfe) - zmortp2 * zfactfe
188               tra(ji,jj,jk,jpdsi) = tra(ji,jj,jk,jpdsi) - zmortp2 * zfactsi
189               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) + zmortp2 * zfactsi
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               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + 0.5 * ztortp2 * zfactfe
193               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + ( zrespp2 + 0.5 * ztortp2 ) * zfactfe
194            END DO
195         END DO
196      END DO
197      !
198      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
199         WRITE(charout, FMT="('diat')")
200         CALL prt_ctl_trc_info(charout)
201         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
202      ENDIF
203      !
204      IF( nn_timing == 1 )  CALL timing_stop('p4z_diat')
205      !
206   END SUBROUTINE p4z_diat
207
208   SUBROUTINE p4z_mort_init
209
210      !!----------------------------------------------------------------------
211      !!                  ***  ROUTINE p4z_mort_init  ***
212      !!
213      !! ** Purpose :   Initialization of phytoplankton parameters
214      !!
215      !! ** Method  :   Read the nampismort namelist and check the parameters
216      !!      called at the first timestep
217      !!
218      !! ** input   :   Namelist nampismort
219      !!
220      !!----------------------------------------------------------------------
221
222      NAMELIST/nampismort/ wchl, wchld, wchldm, mprat, mprat2
223      INTEGER :: ios                 ! Local integer output status for namelist read
224
225      REWIND( numnatp_ref )              ! Namelist nampismort in reference namelist : Pisces phytoplankton
226      READ  ( numnatp_ref, nampismort, IOSTAT = ios, ERR = 901)
227901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismort in reference namelist', lwp )
228
229      REWIND( numnatp_cfg )              ! Namelist nampismort in configuration namelist : Pisces phytoplankton
230      READ  ( numnatp_cfg, nampismort, IOSTAT = ios, ERR = 902 )
231902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismort in configuration namelist', lwp )
232      IF(lwm) WRITE ( numonp, nampismort )
233
234      IF(lwp) THEN                         ! control print
235         WRITE(numout,*) ' '
236         WRITE(numout,*) ' Namelist parameters for phytoplankton mortality, nampismort'
237         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
238         WRITE(numout,*) '    quadratic mortality of phytoplankton      wchl      =', wchl
239         WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchld     =', wchld
240         WRITE(numout,*) '    maximum quadratic mortality of diatoms    wchldm    =', wchldm
241         WRITE(numout,*) '    phytoplankton mortality rate              mprat     =', mprat
242         WRITE(numout,*) '    Diatoms mortality rate                    mprat2    =', mprat2
243      ENDIF
244
245   END SUBROUTINE p4z_mort_init
246
247#else
248   !!======================================================================
249   !!  Dummy module :                                   No PISCES bio-model
250   !!======================================================================
251CONTAINS
252   SUBROUTINE p4z_mort                    ! Empty routine
253   END SUBROUTINE p4z_mort
254#endif 
255
256   !!======================================================================
257END MODULE p4zmort
Note: See TracBrowser for help on using the repository browser.