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.
p4zpoc.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/p4zpoc.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: 35.6 KB
Line 
1MODULE p4zpoc
2   !!======================================================================
3   !!                         ***  MODULE p4zpoc  ***
4   !! TOP :   PISCES Compute remineralization of organic particles
5   !!         Same module for both PISCES and PISCES-QUOTA
6   !!=========================================================================
7   !! History :   1.0  !  2004     (O. Aumont) Original code
8   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
9   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron
10   !!             3.6  !  2016-03  (O. Aumont) Quota model and diverse
11   !!             4.0  !  2018     (O. Aumont) Variable lability parameterization
12   !!----------------------------------------------------------------------
13   !!   p4z_poc       :  Compute remineralization/dissolution of organic compounds
14   !!   p4z_poc_init  :  Initialisation of parameters for remineralisation
15   !!   alngam and gamain : computation of the incomplete gamma function
16   !!----------------------------------------------------------------------
17   USE oce_trc         !  shared variables between ocean and passive tracers
18   USE trc             !  passive tracers common variables
19   USE sms_pisces      !  PISCES Source Minus Sink variables
20   USE prtctl_trc      !  print control for debugging
21   USE iom             !  I/O manager
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   p4z_poc         ! called in p4zbio.F90
27   PUBLIC   p4z_poc_init    ! called in trcini_pisces.F90
28   PUBLIC   alngam          !
29   PUBLIC   gamain          !
30
31   REAL(wp), PUBLIC ::   xremip     !: remineralisation rate of DOC
32   REAL(wp), PUBLIC ::   xremipc    !: remineralisation rate of DOC
33   REAL(wp), PUBLIC ::   xremipn    !: remineralisation rate of DON
34   REAL(wp), PUBLIC ::   xremipp    !: remineralisation rate of DOP
35   INTEGER , PUBLIC ::   jcpoc      !: number of lability classes
36   REAL(wp), PUBLIC ::   rshape     !: shape factor of the gamma distribution
37
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)       ::   alphan, reminp   !: variable lability of POC and initial distribution
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   alphap           !: lability distribution of small particles
40
41
42   !!----------------------------------------------------------------------
43   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
44   !! $Id$
45   !! Software governed by the CeCILL license (see ./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE p4z_poc( kt, knt )
50      !!---------------------------------------------------------------------
51      !!                     ***  ROUTINE p4z_poc  ***
52      !!
53      !! ** Purpose :   Compute remineralization of organic particles
54      !!                A reactivity-continuum parameterization is chosen
55      !!                to describe the lability of the organic particles
56      !!                As a consequence, the remineralisation rates of the
57      !!                the different pools change with time as a function of
58      !!                the lability distribution
59      !!
60      !! ** Method  : - Computation of the remineralisation rates is performed
61      !!                according to reactivity continuum formalism described
62      !!                in Aumont et al. (2017).
63      !!---------------------------------------------------------------------
64      INTEGER, INTENT(in) ::   kt, knt   ! ocean time step and ???
65      !
66      INTEGER  ::   ji, jj, jk, jn
67      REAL(wp) ::   zremip, zremig, zdep, zorem, zorem2, zofer
68      REAL(wp) ::   zopon, zopop, zopoc, zopoc2, zopon2, zopop2
69      REAL(wp) ::   zsizek, zsizek1, alphat, remint, solgoc, zpoc
70      REAL(wp) ::   zofer2, zofer3
71      REAL(wp) ::   zrfact2
72      CHARACTER (len=25) :: charout
73      REAL(wp), DIMENSION(jpi,jpj  )   :: totprod, totthick, totcons 
74      REAL(wp), DIMENSION(jpi,jpj,jpk)   :: zremipoc, zremigoc, zorem3, ztremint, zfolimi
75      REAL(wp), DIMENSION(jpi,jpj,jpk,jcpoc) :: alphag
76      !!---------------------------------------------------------------------
77      !
78      IF( ln_timing )  CALL timing_start('p4z_poc')
79      !
80      ! Initialization of local variables
81      ! ---------------------------------
82
83      ! Here we compute the GOC -> POC rate due to the shrinking
84      ! of the fecal pellets/aggregates as a result of bacterial
85      ! solubilization
86      ! This is based on a fractal dimension of 2.56 and a spectral
87      ! slope of -3.6 (identical to what is used in p4zsink to compute
88      ! aggregation
89      solgoc = 0.04/ 2.56 * 1./ ( 1.-50**(-0.04) )
90
91      ! Initialisation of temporary arrays
92      IF( ln_p4z ) THEN
93         zremipoc(:,:,:) = xremip
94         zremigoc(:,:,:) = xremip
95      ELSE    ! ln_p5z
96         zremipoc(:,:,:) = xremipc
97         zremigoc(:,:,:) = xremipc
98      ENDIF
99      zorem3(:,:,:)   = 0.
100      orem  (:,:,:)   = 0.
101      ztremint(:,:,:) = 0.
102      zfolimi (:,:,:) = 0.
103
104      ! Initialisation of the lability distributions that are set to
105      ! the distribution of newly produced organic particles
106      DO jn = 1, jcpoc
107        alphag(:,:,:,jn) = alphan(jn)
108        alphap(:,:,:,jn) = alphan(jn)
109      END DO
110
111     ! Lability parameterization. This is the big particles part (GOC)
112     ! This lability parameterization is always active. However, if only one
113     ! lability class is specified in the namelist, this is equivalent to
114     ! a standard parameterisation with a constant lability
115     ! -----------------------------------------------------------------------
116     ztremint(:,:,:) = zremigoc(:,:,:)
117     DO jk = 2, jpkm1
118        DO jj = 1, jpj
119           DO ji = 1, jpi
120              IF (tmask(ji,jj,jk) == 1.) THEN
121                zdep = hmld(ji,jj)
122
123                ! In the case of GOC, lability is constant in the mixed layer
124                ! It is computed only below the mixed layer depth
125                ! ------------------------------------------------------------
126                IF( gdept_n(ji,jj,jk) > zdep ) THEN
127                  alphat = 0.
128                  remint = 0.
129                  !
130                  zsizek1  = e3t_n(ji,jj,jk-1) / 2. / (wsbio4(ji,jj,jk-1) + rtrn) * tgfunc(ji,jj,jk-1)
131                  zsizek = e3t_n(ji,jj,jk) / 2. / (wsbio4(ji,jj,jk) + rtrn) * tgfunc(ji,jj,jk)
132                  !
133                  IF ( gdept_n(ji,jj,jk-1) <= zdep ) THEN
134                    !
135                    ! The first level just below the mixed layer needs a
136                    ! specific treatment because lability is supposed constant
137                    ! everywhere within the mixed layer. This means that
138                    ! change in lability in the bottom part of the previous cell
139                    ! should not be computed
140                    ! ----------------------------------------------------------
141                    !
142                    ! POC concentration is computed using the lagrangian
143                    ! framework. It is only used for the lability param
144                    zpoc = trb(ji,jj,jk-1,jpgoc) + consgoc(ji,jj,jk) * rday / rfact2               &
145                    &   * e3t_n(ji,jj,jk) / 2. / (wsbio4(ji,jj,jk) + rtrn)
146                    zpoc = MAX(0., zpoc)
147                    !
148                    DO jn = 1, jcpoc
149                       !
150                       ! Lagrangian based algorithm. The fraction of each
151                       ! lability class is computed starting from the previous
152                       ! level
153                       ! -----------------------------------------------------
154                       !
155                       ! the concentration of each lability class is calculated
156                       ! as the sum of the different sources and sinks
157                       ! Please note that production of new GOC experiences
158                       ! degradation
159                       alphag(ji,jj,jk,jn) = alphag(ji,jj,jk-1,jn) * exp( -reminp(jn) * zsizek ) * zpoc &
160                       &   + prodgoc(ji,jj,jk) * alphan(jn) / tgfunc(ji,jj,jk) / reminp(jn)             &
161                       &   * ( 1. - exp( -reminp(jn) * zsizek ) ) * rday / rfact2 
162                       alphat = alphat + alphag(ji,jj,jk,jn)
163                       remint = remint + alphag(ji,jj,jk,jn) * reminp(jn)
164                    END DO
165                  ELSE
166
167                    ! standard algorithm in the rest of the water column
168                    ! See the comments in the previous block.
169                    ! ---------------------------------------------------
170                    zpoc = trb(ji,jj,jk-1,jpgoc) + consgoc(ji,jj,jk-1) * rday / rfact2               &
171                    &   * e3t_n(ji,jj,jk-1) / 2. / (wsbio4(ji,jj,jk-1) + rtrn) + consgoc(ji,jj,jk)   &
172                    &   * rday / rfact2 * e3t_n(ji,jj,jk) / 2. / (wsbio4(ji,jj,jk) + rtrn)
173                    zpoc = max(0., zpoc)
174                    !
175                    DO jn = 1, jcpoc
176                       alphag(ji,jj,jk,jn) = alphag(ji,jj,jk-1,jn) * exp( -reminp(jn) * ( zsizek              &
177                       &   + zsizek1 ) ) * zpoc + ( prodgoc(ji,jj,jk-1) / tgfunc(ji,jj,jk-1) * ( 1.           &
178                       &   - exp( -reminp(jn) * zsizek1 ) ) * exp( -reminp(jn) * zsizek ) + prodgoc(ji,jj,jk) &
179                       &   / tgfunc(ji,jj,jk) * ( 1. - exp( -reminp(jn) * zsizek ) ) ) * rday / rfact2 / reminp(jn) * alphan(jn) 
180                       alphat = alphat + alphag(ji,jj,jk,jn)
181                       remint = remint + alphag(ji,jj,jk,jn) * reminp(jn)
182                    END DO
183                  ENDIF
184                  !
185                  DO jn = 1, jcpoc
186                     ! The contribution of each lability class at the current
187                     ! level is computed
188                     alphag(ji,jj,jk,jn) = alphag(ji,jj,jk,jn) / ( alphat + rtrn)
189                  END DO
190                  ! Computation of the mean remineralisation rate
191                  ztremint(ji,jj,jk) =  MAX(0., remint / ( alphat + rtrn) )
192                  !
193                ENDIF
194              ENDIF
195            END DO
196         END DO
197      END DO
198
199      IF( ln_p4z ) THEN   ;   zremigoc(:,:,:) = MIN( xremip , ztremint(:,:,:) )
200      ELSE                ;   zremigoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) )
201      ENDIF
202
203      IF( ln_p4z ) THEN
204         ! The standard PISCES part
205         DO jk = 1, jpkm1
206            DO jj = 1, jpj
207               DO ji = 1, jpi
208                  ! POC degradation by bacterial activity. It is a function
209                  ! of the mean lability and of temperature. This also includes
210                  ! shrinking of particles due to the bacterial activity
211                  ! -----------------------------------------------------------
212                  zremig = zremigoc(ji,jj,jk) * xstep * tgfunc(ji,jj,jk)
213                  zorem2  = zremig * trb(ji,jj,jk,jpgoc)
214                  orem(ji,jj,jk)      = zorem2
215                  zorem3(ji,jj,jk) = zremig * solgoc * trb(ji,jj,jk,jpgoc)
216                  zofer2 = zremig * trb(ji,jj,jk,jpbfe)
217                  zofer3 = zremig * solgoc * trb(ji,jj,jk,jpbfe)
218
219                  ! update of the TRA arrays
220                  tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + zorem3(ji,jj,jk)
221                  tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) - zorem2 - zorem3(ji,jj,jk)
222                  tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zofer3
223                  tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) - zofer2 - zofer3
224                  tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zorem2
225                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zofer2
226                  zfolimi(ji,jj,jk)   = zofer2
227               END DO
228            END DO
229         END DO
230      ELSE
231         ! PISCES-QUOTA part
232         DO jk = 1, jpkm1
233            DO jj = 1, jpj
234               DO ji = 1, jpi
235                  ! POC disaggregation by bacterial activity. It is a function
236                  ! of the mean lability and of temperature. Shrinking of
237                  ! particles due to the bacterial activity is also included
238                  ! ----------------------------------------------------------
239                  zremig = zremigoc(ji,jj,jk) * xstep * tgfunc(ji,jj,jk)
240                  zopoc2 = zremig  * trb(ji,jj,jk,jpgoc)
241                  orem(ji,jj,jk) = zopoc2
242                  zorem3(ji,jj,jk) = zremig * solgoc * trb(ji,jj,jk,jpgoc)
243                  zopon2 = xremipn / xremipc * zremig * trb(ji,jj,jk,jpgon)
244                  zopop2 = xremipp / xremipc * zremig * trb(ji,jj,jk,jpgop)
245                  zofer2 = xremipn / xremipc * zremig * trb(ji,jj,jk,jpbfe)
246
247                  ! Update of the TRA arrays
248                  tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) + zorem3(ji,jj,jk)
249                  tra(ji,jj,jk,jppon) = tra(ji,jj,jk,jppon) + solgoc * zopon2 
250                  tra(ji,jj,jk,jppop) = tra(ji,jj,jk,jppop) + solgoc * zopop2
251                  tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + solgoc * zofer2
252                  tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zopoc2
253                  tra(ji,jj,jk,jpdon) = tra(ji,jj,jk,jpdon) + zopon2
254                  tra(ji,jj,jk,jpdop) = tra(ji,jj,jk,jpdop) + zopop2
255                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zofer2
256                  tra(ji,jj,jk,jpgoc) = tra(ji,jj,jk,jpgoc) - zopoc2 - zorem3(ji,jj,jk)
257                  tra(ji,jj,jk,jpgon) = tra(ji,jj,jk,jpgon) - zopon2 * (1. + solgoc)
258                  tra(ji,jj,jk,jpgop) = tra(ji,jj,jk,jpgop) - zopop2 * (1. + solgoc)
259                  tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) - zofer2 * (1. + solgoc)
260                  zfolimi(ji,jj,jk)   = zofer2
261               END DO
262            END DO
263         END DO
264      ENDIF
265
266     IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
267        WRITE(charout, FMT="('poc1')")
268        CALL prt_ctl_trc_info(charout)
269        CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
270     ENDIF
271
272     ! Lability parameterization for the small OM particles. This param
273     ! is based on the same theoretical background as the big particles.
274     ! However, because of its low sinking speed, lability is not supposed
275     ! to be equal to its initial value (the value of the freshly produced
276     ! organic matter) in the MLD. It is however uniform in the mixed layer.
277     ! ---------------------------------------------------------------------
278     totprod (:,:) = 0.
279     totthick(:,:) = 0.
280     totcons (:,:) = 0.
281
282     ! intregrated production and consumption of POC in the mixed layer
283     ! ----------------------------------------------------------------
284     DO jk = 1, jpkm1
285        DO jj = 1, jpj
286           DO ji = 1, jpi
287              zdep = hmld(ji,jj)
288              IF (tmask(ji,jj,jk) == 1. .AND. gdept_n(ji,jj,jk) <= zdep ) THEN
289                totprod(ji,jj) = totprod(ji,jj) + prodpoc(ji,jj,jk) * e3t_n(ji,jj,jk) * rday/ rfact2
290                ! The temperature effect is included here
291                totthick(ji,jj) = totthick(ji,jj) + e3t_n(ji,jj,jk)* tgfunc(ji,jj,jk)
292                totcons(ji,jj) = totcons(ji,jj) - conspoc(ji,jj,jk) * e3t_n(ji,jj,jk) * rday/ rfact2    &
293                &                / ( trb(ji,jj,jk,jppoc) + rtrn )
294              ENDIF
295           END DO
296        END DO
297     END DO
298
299     ! Computation of the lability spectrum in the mixed layer. In the mixed
300     ! layer, this spectrum is supposed to be uniform as a result of intense
301     ! mixing.
302     ! ---------------------------------------------------------------------
303     ztremint(:,:,:) = zremipoc(:,:,:)
304     DO jk = 1, jpkm1
305        DO jj = 1, jpj
306           DO ji = 1, jpi
307              IF (tmask(ji,jj,jk) == 1.) THEN
308                zdep = hmld(ji,jj)
309                alphat = 0.0
310                remint = 0.0
311                IF( gdept_n(ji,jj,jk) <= zdep ) THEN
312                   DO jn = 1, jcpoc
313                      ! For each lability class, the system is supposed to be
314                      ! at equilibrium: Prod - Sink - w alphap = 0.
315                      alphap(ji,jj,jk,jn) = totprod(ji,jj) * alphan(jn) / ( reminp(jn)    &
316                      &                     * totthick(ji,jj) + totcons(ji,jj) + wsbio + rtrn )
317                      alphat = alphat + alphap(ji,jj,jk,jn)
318                   END DO
319                   DO jn = 1, jcpoc
320                      alphap(ji,jj,jk,jn) = alphap(ji,jj,jk,jn) / ( alphat + rtrn)
321                      remint = remint + alphap(ji,jj,jk,jn) * reminp(jn)
322                   END DO
323                   ! Mean remineralization rate in the mixed layer
324                   ztremint(ji,jj,jk) =  MAX( 0., remint )
325                ENDIF
326              ENDIF
327           END DO
328        END DO
329     END DO
330     !
331     IF( ln_p4z ) THEN   ;  zremipoc(:,:,:) = MIN( xremip , ztremint(:,:,:) )
332     ELSE                ;  zremipoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) )
333     ENDIF
334
335     ! The lability parameterization is used here. The code is here
336     ! almost identical to what is done for big particles. The only difference
337     ! is that an additional source from GOC to POC is included. This means
338     ! that since we need the lability spectrum of GOC, GOC spectrum
339     ! should be determined before.
340     ! -----------------------------------------------------------------------
341     DO jk = 2, jpkm1
342        DO jj = 1, jpj
343           DO ji = 1, jpi
344              IF (tmask(ji,jj,jk) == 1.) THEN
345                zdep = hmld(ji,jj)
346                IF( gdept_n(ji,jj,jk) > zdep ) THEN
347                  alphat = 0.
348                  remint = 0.
349                  ! the scale factors are corrected with temperature
350                  zsizek1  = e3t_n(ji,jj,jk-1) / 2. / (wsbio3(ji,jj,jk-1) + rtrn) * tgfunc(ji,jj,jk-1)
351                  zsizek = e3t_n(ji,jj,jk) / 2. / (wsbio3(ji,jj,jk) + rtrn) * tgfunc(ji,jj,jk)
352
353                  ! Special treatment of the level just below the MXL
354                  ! See the comments in the GOC section
355                  ! ---------------------------------------------------
356                  IF ( gdept_n(ji,jj,jk-1) <= zdep ) THEN
357                    !
358                    ! Computation of the POC concentration using the
359                    ! lagrangian algorithm
360                    zpoc = trb(ji,jj,jk-1,jppoc) + conspoc(ji,jj,jk) * rday / rfact2               &
361                    &   * e3t_n(ji,jj,jk) / 2. / (wsbio3(ji,jj,jk) + rtrn)
362                    zpoc = max(0., zpoc)
363                    !
364                    DO jn = 1, jcpoc
365                       ! computation of the lability spectrum applying the
366                       ! different sources and sinks
367                       alphap(ji,jj,jk,jn) = alphap(ji,jj,jk-1,jn) * exp( -reminp(jn) * zsizek ) * zpoc  &
368                       &   + ( prodpoc(ji,jj,jk) * alphan(jn) + zorem3(ji,jj,jk) * alphag(ji,jj,jk,jn) ) &
369                       &   / tgfunc(ji,jj,jk) / reminp(jn) * rday / rfact2 * ( 1. - exp( -reminp(jn)     &
370                       &   * zsizek ) )
371                       alphap(ji,jj,jk,jn) = MAX( 0., alphap(ji,jj,jk,jn) )
372                       alphat = alphat + alphap(ji,jj,jk,jn)
373                    END DO
374                  ELSE
375
376                    ! Lability parameterization for the interior of the ocean
377                    ! This is very similar to what is done in the previous
378                    ! block
379                    ! --------------------------------------------------------
380                    zpoc = trb(ji,jj,jk-1,jppoc) + conspoc(ji,jj,jk-1) * rday / rfact2               &
381                    &   * e3t_n(ji,jj,jk-1) / 2. / (wsbio3(ji,jj,jk-1) + rtrn) + conspoc(ji,jj,jk)   &
382                    &   * rday / rfact2 * e3t_n(ji,jj,jk) / 2. / (wsbio3(ji,jj,jk) + rtrn)
383                    zpoc = max(0., zpoc)
384                    !
385                    DO jn = 1, jcpoc
386                       alphap(ji,jj,jk,jn) = alphap(ji,jj,jk-1,jn) * exp( -reminp(jn)                       &
387                       &   * ( zsizek + zsizek1 ) ) * zpoc + ( prodpoc(ji,jj,jk-1) * alphan(jn)             & 
388                       &   + zorem3(ji,jj,jk-1) * alphag(ji,jj,jk-1,jn) ) * rday / rfact2 / reminp(jn)      &
389                       &   / tgfunc(ji,jj,jk-1) * ( 1. - exp( -reminp(jn) * zsizek1 ) ) * exp( -reminp(jn)  &
390                       &   * zsizek ) + ( prodpoc(ji,jj,jk) * alphan(jn) + zorem3(ji,jj,jk)                 &
391                       &   * alphag(ji,jj,jk,jn) ) * rday / rfact2 / reminp(jn) / tgfunc(ji,jj,jk) * ( 1.   &
392                       &   - exp( -reminp(jn) * zsizek ) )
393                       alphap(ji,jj,jk,jn) = max(0., alphap(ji,jj,jk,jn) )
394                       alphat = alphat + alphap(ji,jj,jk,jn)
395                    END DO
396                  ENDIF
397                  ! Normalization of the lability spectrum so that the
398                  ! integral is equal to 1
399                  DO jn = 1, jcpoc
400                     alphap(ji,jj,jk,jn) = alphap(ji,jj,jk,jn) / ( alphat + rtrn)
401                     remint = remint + alphap(ji,jj,jk,jn) * reminp(jn)
402                  END DO
403                  ! Mean remineralization rate in the water column
404                  ztremint(ji,jj,jk) =  MAX( 0., remint )
405                ENDIF
406              ENDIF
407            END DO
408         END DO
409      END DO
410
411     IF( ln_p4z ) THEN   ;   zremipoc(:,:,:) = MIN( xremip , ztremint(:,:,:) )
412     ELSE                ;   zremipoc(:,:,:) = MIN( xremipc, ztremint(:,:,:) )
413     ENDIF
414
415     IF( ln_p4z ) THEN
416        ! Standard PISCES part
417        DO jk = 1, jpkm1
418           DO jj = 1, jpj
419              DO ji = 1, jpi
420                 IF (tmask(ji,jj,jk) == 1.) THEN
421                    ! POC solubilisation by bacterial activity. It is a function
422                    ! of the mean lability and of temperature
423                    ! ----------------------------------------------------------
424                    zremip          = zremipoc(ji,jj,jk) * xstep * tgfunc(ji,jj,jk)
425                    zorem           = zremip * trb(ji,jj,jk,jppoc)
426                    zofer           = zremip * trb(ji,jj,jk,jpsfe)
427
428                    ! Update of the TRA arrays
429                    tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zorem
430                    orem(ji,jj,jk)      = orem(ji,jj,jk) + zorem
431                    tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zofer
432                    tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) - zorem
433                    tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) - zofer
434                    zfolimi(ji,jj,jk)   = zfolimi(ji,jj,jk) + zofer
435                 ENDIF
436              END DO
437           END DO
438        END DO
439     ELSE
440        ! PISCES QUOTA part
441        DO jk = 1, jpkm1
442           DO jj = 1, jpj
443              DO ji = 1, jpi
444                 ! POC disaggregation by bacterial activity. It is a function
445                 ! of the mean lability and of temperature
446                 ! ----------------------------------------------------------
447                 zremip = zremipoc(ji,jj,jk) * xstep * tgfunc(ji,jj,jk)
448                 zopoc  = zremip * trb(ji,jj,jk,jppoc)
449                 orem(ji,jj,jk)  = orem(ji,jj,jk) + zopoc
450                 zopon  = xremipn / xremipc * zremip * trb(ji,jj,jk,jppon)
451                 zopop  = xremipp / xremipc * zremip * trb(ji,jj,jk,jppop)
452                 zofer  = xremipn / xremipc * zremip * trb(ji,jj,jk,jpsfe)
453
454                 tra(ji,jj,jk,jppoc) = tra(ji,jj,jk,jppoc) - zopoc
455                 tra(ji,jj,jk,jppon) = tra(ji,jj,jk,jppon) - zopon
456                 tra(ji,jj,jk,jppop) = tra(ji,jj,jk,jppop) - zopop
457                 tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) - zofer
458                 tra(ji,jj,jk,jpdoc) = tra(ji,jj,jk,jpdoc) + zopoc
459                 tra(ji,jj,jk,jpdon) = tra(ji,jj,jk,jpdon) + zopon 
460                 tra(ji,jj,jk,jpdop) = tra(ji,jj,jk,jpdop) + zopop 
461                 tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zofer 
462                 zfolimi(ji,jj,jk)   = zfolimi(ji,jj,jk) + zofer
463              END DO
464           END DO
465        END DO
466     ENDIF
467
468     IF( lk_iomput ) THEN
469        IF( knt == nrdttrc ) THEN
470          zrfact2 = 1.e3 * rfact2r
471          CALL iom_put( "REMINP" , zremipoc(:,:,:) * tmask(:,:,:) )  ! Remineralisation rate of small particles
472          CALL iom_put( "REMING" , zremigoc(:,:,:) * tmask(:,:,:) )  ! Remineralisation rate of large particles
473          CALL iom_put( "REMINF" , zfolimi(:,:,:)  * tmask(:,:,:)  * 1.e+9 * zrfact2 )  ! Remineralisation of biogenic particulate iron
474        ENDIF
475     ENDIF
476
477      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
478         WRITE(charout, FMT="('poc2')")
479         CALL prt_ctl_trc_info(charout)
480         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
481      ENDIF
482      !
483      !
484      IF( ln_timing )   CALL timing_stop('p4z_poc')
485      !
486   END SUBROUTINE p4z_poc
487
488
489   SUBROUTINE p4z_poc_init
490      !!----------------------------------------------------------------------
491      !!                  ***  ROUTINE p4z_poc_init  ***
492      !!
493      !! ** Purpose :   Initialization of remineralization parameters
494      !!
495      !! ** Method  :   Read the nampispoc namelist and check the parameters
496      !!              called at the first timestep
497      !!
498      !! ** input   :   Namelist nampispoc
499      !!----------------------------------------------------------------------
500      INTEGER ::   jn            ! dummy loop index
501      INTEGER ::   ios, ifault   ! Local integer
502      REAL(wp)::   remindelta, reminup, remindown
503      !!
504      NAMELIST/nampispoc/ xremip , jcpoc  , rshape,  &
505         &                xremipc, xremipn, xremipp
506      !!----------------------------------------------------------------------
507      !
508      IF(lwp) THEN
509         WRITE(numout,*)
510         WRITE(numout,*) 'p4z_poc_init : Initialization of remineralization parameters'
511         WRITE(numout,*) '~~~~~~~~~~~~'
512      ENDIF
513      !
514      REWIND( numnatp_ref )              ! Namelist nampisrem in reference namelist : Pisces remineralization
515      READ  ( numnatp_ref, nampispoc, IOSTAT = ios, ERR = 901)
516901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampispoc in reference namelist' )
517      REWIND( numnatp_cfg )              ! Namelist nampisrem in configuration namelist : Pisces remineralization
518      READ  ( numnatp_cfg, nampispoc, IOSTAT = ios, ERR = 902 )
519902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampispoc in configuration namelist' )
520      IF(lwm) WRITE( numonp, nampispoc )
521
522      IF(lwp) THEN                         ! control print
523         WRITE(numout,*) '   Namelist : nampispoc'
524         IF( ln_p4z ) THEN
525            WRITE(numout,*) '      remineralisation rate of POC              xremip    =', xremip
526         ELSE
527            WRITE(numout,*) '      remineralisation rate of POC              xremipc   =', xremipc
528            WRITE(numout,*) '      remineralisation rate of PON              xremipn   =', xremipn
529            WRITE(numout,*) '      remineralisation rate of POP              xremipp   =', xremipp
530         ENDIF
531         WRITE(numout,*) '      Number of lability classes for POC        jcpoc     =', jcpoc
532         WRITE(numout,*) '      Shape factor of the gamma distribution    rshape    =', rshape
533      ENDIF
534      !
535      ! Discretization along the lability space
536      ! ---------------------------------------
537      !
538      ALLOCATE( alphan(jcpoc) , reminp(jcpoc) , alphap(jpi,jpj,jpk,jcpoc) )
539      !
540      IF (jcpoc > 1) THEN  ! Case when more than one lability class is used
541         !
542         remindelta = LOG(4. * 1000. ) / REAL(jcpoc-1, wp)
543         reminup = 1./ 400. * EXP(remindelta)
544         !
545         ! Discretization based on incomplete gamma functions
546         ! As incomplete gamma functions are not available in standard
547         ! fortran 95, they have been coded as functions in this module (gamain)
548         ! ---------------------------------------------------------------------
549         !
550         alphan(1) = gamain(reminup, rshape, ifault)
551         reminp(1) = gamain(reminup, rshape+1.0, ifault) * xremip / alphan(1)
552         DO jn = 2, jcpoc-1
553            reminup = 1./ 400. * EXP( REAL(jn, wp) * remindelta)
554            remindown = 1. / 400. * EXP( REAL(jn-1, wp) * remindelta)
555            alphan(jn) = gamain(reminup, rshape, ifault) - gamain(remindown, rshape, ifault)
556            reminp(jn) = gamain(reminup, rshape+1.0, ifault) - gamain(remindown, rshape+1.0, ifault)
557            reminp(jn) = reminp(jn) * xremip / alphan(jn)
558         END DO
559         remindown = 1. / 400. * EXP( REAL(jcpoc-1, wp) * remindelta)
560         alphan(jcpoc) = 1.0 - gamain(remindown, rshape, ifault)
561         reminp(jcpoc) = 1.0 - gamain(remindown, rshape+1.0, ifault)
562         reminp(jcpoc) = reminp(jcpoc) * xremip / alphan(jcpoc)
563
564      ELSE  ! Only one lability class is used
565         alphan(jcpoc) = 1.
566         reminp(jcpoc) = xremip
567      ENDIF
568
569      DO jn = 1, jcpoc
570         alphap(:,:,:,jn) = alphan(jn)
571      END DO
572
573   END SUBROUTINE p4z_poc_init
574
575
576   REAL FUNCTION alngam( xvalue, ifault )
577      !*****************************************************************************80
578      !
579      !! ALNGAM computes the logarithm of the gamma function.
580      !
581      !  Modified:    13 January 2008
582      !
583      !  Author  :    Allan Macleod
584      !               FORTRAN90 version by John Burkardt
585      !
586      !  Reference:
587      !    Allan Macleod, Algorithm AS 245,
588      !    A Robust and Reliable Algorithm for the Logarithm of the Gamma Function,
589      !    Applied Statistics,
590      !    Volume 38, Number 2, 1989, pages 397-402.
591      !
592      !  Parameters:
593      !
594      !    Input, real ( kind = 8 ) XVALUE, the argument of the Gamma function.
595      !
596      !    Output, integer ( kind = 4 ) IFAULT, error flag.
597      !    0, no error occurred.
598      !    1, XVALUE is less than or equal to 0.
599      !    2, XVALUE is too big.
600      !
601      !    Output, real ( kind = 8 ) ALNGAM, the logarithm of the gamma function of X.
602      !*****************************************************************************80
603  implicit none
604
605  real(wp), parameter :: alr2pi = 0.918938533204673E+00
606  integer:: ifault
607  real(wp), dimension ( 9 ) :: r1 = (/ &
608    -2.66685511495E+00, &
609    -24.4387534237E+00, &
610    -21.9698958928E+00, &
611     11.1667541262E+00, &
612     3.13060547623E+00, &
613     0.607771387771E+00, &
614     11.9400905721E+00, &
615     31.4690115749E+00, &
616     15.2346874070E+00 /)
617  real(wp), dimension ( 9 ) :: r2 = (/ &
618    -78.3359299449E+00, &
619    -142.046296688E+00, &
620     137.519416416E+00, &
621     78.6994924154E+00, &
622     4.16438922228E+00, &
623     47.0668766060E+00, &
624     313.399215894E+00, &
625     263.505074721E+00, &
626     43.3400022514E+00 /)
627  real(wp), dimension ( 9 ) :: r3 = (/ &
628    -2.12159572323E+05, &
629     2.30661510616E+05, &
630     2.74647644705E+04, &
631    -4.02621119975E+04, &
632    -2.29660729780E+03, &
633    -1.16328495004E+05, &
634    -1.46025937511E+05, &
635    -2.42357409629E+04, &
636    -5.70691009324E+02 /)
637  real(wp), dimension ( 5 ) :: r4 = (/ &
638     0.279195317918525E+00, &
639     0.4917317610505968E+00, &
640     0.0692910599291889E+00, &
641     3.350343815022304E+00, &
642     6.012459259764103E+00 /)
643  real (wp) :: x
644  real (wp) :: x1
645  real (wp) :: x2
646  real (wp), parameter :: xlge = 5.10E+05
647  real (wp), parameter :: xlgst = 1.0E+30
648  real (wp) :: xvalue
649  real (wp) :: y
650
651  x = xvalue
652  alngam = 0.0E+00
653!
654!  Check the input.
655!
656  if ( xlgst <= x ) then
657    ifault = 2
658    return
659  end if
660  if ( x <= 0.0E+00 ) then
661    ifault = 1
662    return
663  end if
664
665  ifault = 0
666!
667!  Calculation for 0 < X < 0.5 and 0.5 <= X < 1.5 combined.
668!
669  if ( x < 1.5E+00 ) then
670
671    if ( x < 0.5E+00 ) then
672      alngam = - log ( x )
673      y = x + 1.0E+00
674!
675!  Test whether X < machine epsilon.
676!
677      if ( y == 1.0E+00 ) then
678        return
679      end if
680
681    else
682
683      alngam = 0.0E+00
684      y = x
685      x = ( x - 0.5E+00 ) - 0.5E+00
686
687    end if
688
689    alngam = alngam + x * (((( &
690        r1(5)   * y &
691      + r1(4) ) * y &
692      + r1(3) ) * y &
693      + r1(2) ) * y &
694      + r1(1) ) / (((( &
695                  y &
696      + r1(9) ) * y &
697      + r1(8) ) * y &
698      + r1(7) ) * y &
699      + r1(6) )
700
701    return
702
703  end if
704!
705!  Calculation for 1.5 <= X < 4.0.
706!
707  if ( x < 4.0E+00 ) then
708
709    y = ( x - 1.0E+00 ) - 1.0E+00
710
711    alngam = y * (((( &
712        r2(5)   * x &
713      + r2(4) ) * x &
714      + r2(3) ) * x &
715      + r2(2) ) * x &
716      + r2(1) ) / (((( &
717                  x &
718      + r2(9) ) * x &
719      + r2(8) ) * x &
720      + r2(7) ) * x &
721      + r2(6) )
722!
723!  Calculation for 4.0 <= X < 12.0.
724!
725  else if ( x < 12.0E+00 ) then
726
727    alngam = (((( &
728        r3(5)   * x &
729      + r3(4) ) * x &
730      + r3(3) ) * x &
731      + r3(2) ) * x &
732      + r3(1) ) / (((( &
733                  x &
734      + r3(9) ) * x &
735      + r3(8) ) * x &
736      + r3(7) ) * x &
737      + r3(6) )
738!
739!  Calculation for 12.0 <= X.
740!
741  else
742
743    y = log ( x )
744    alngam = x * ( y - 1.0E+00 ) - 0.5E+00 * y + alr2pi
745
746    if ( x <= xlge ) then
747
748      x1 = 1.0E+00 / x
749      x2 = x1 * x1
750
751      alngam = alngam + x1 * ( ( &
752             r4(3)   * &
753        x2 + r4(2) ) * &
754        x2 + r4(1) ) / ( ( &
755        x2 + r4(5) ) * &
756        x2 + r4(4) )
757
758    end if
759
760   end if
761
762   END FUNCTION alngam
763
764
765   REAL FUNCTION gamain( x, p, ifault )
766!*****************************************************************************80
767!
768!! GAMAIN computes the incomplete gamma ratio.
769!
770!  Discussion:
771!
772!    A series expansion is used if P > X or X <= 1.  Otherwise, a
773!    continued fraction approximation is used.
774!
775!  Modified:
776!
777!    17 January 2008
778!
779!  Author:
780!
781!    G Bhattacharjee
782!    FORTRAN90 version by John Burkardt
783!
784!  Reference:
785!
786!    G Bhattacharjee,
787!    Algorithm AS 32:
788!    The Incomplete Gamma Integral,
789!    Applied Statistics,
790!    Volume 19, Number 3, 1970, pages 285-287.
791!
792!  Parameters:
793!
794!    Input, real ( kind = 8 ) X, P, the parameters of the incomplete
795!    gamma ratio.  0 <= X, and 0 < P.
796!
797!    Output, integer ( kind = 4 ) IFAULT, error flag.
798!    0, no errors.
799!    1, P <= 0.
800!    2, X < 0.
801!    3, underflow.
802!    4, error return from the Log Gamma routine.
803!
804!    Output, real ( kind = 8 ) GAMAIN, the value of the incomplete
805!    gamma ratio.
806!
807  implicit none
808
809  real (wp) a
810  real (wp), parameter :: acu = 1.0E-08
811  real (wp) an
812  real (wp) arg
813  real (wp) b
814  real (wp) dif
815  real (wp) factor
816  real (wp) g
817  real (wp) gin
818  integer i
819  integer ifault
820  real (wp), parameter :: oflo = 1.0E+37
821  real (wp) p
822  real (wp) pn(6)
823  real (wp) rn
824  real (wp) term
825  real (wp), parameter :: uflo = 1.0E-37
826  real (wp) x
827!
828!  Check the input.
829!
830  if ( p <= 0.0E+00 ) then
831    ifault = 1
832    gamain = 0.0E+00
833    return
834  end if
835
836  if ( x < 0.0E+00 ) then
837    ifault = 2
838    gamain = 0.0E+00
839    return
840  end if
841
842  if ( x == 0.0E+00 ) then
843    ifault = 0
844    gamain = 0.0E+00
845    return
846  end if
847
848  g = alngam ( p, ifault )
849
850  if ( ifault /= 0 ) then
851    ifault = 4
852    gamain = 0.0E+00
853    return
854  end if
855
856  arg = p * log ( x ) - x - g
857
858  if ( arg < log ( uflo ) ) then
859    ifault = 3
860    gamain = 0.0E+00
861    return
862  end if
863
864  ifault = 0
865  factor = exp ( arg )
866!
867!  Calculation by series expansion.
868!
869  if ( x <= 1.0E+00 .or. x < p ) then
870
871    gin = 1.0E+00
872    term = 1.0E+00
873    rn = p
874
875    do
876
877      rn = rn + 1.0E+00
878      term = term * x / rn
879      gin = gin + term
880
881      if ( term <= acu ) then
882        exit
883      end if
884
885    end do
886
887    gamain = gin * factor / p
888    return
889
890  end if
891!
892!  Calculation by continued fraction.
893!
894  a = 1.0E+00 - p
895  b = a + x + 1.0E+00
896  term = 0.0E+00
897
898  pn(1) = 1.0E+00
899  pn(2) = x
900  pn(3) = x + 1.0E+00
901  pn(4) = x * b
902
903  gin = pn(3) / pn(4)
904
905  do
906
907    a = a + 1.0E+00
908    b = b + 2.0E+00
909    term = term + 1.0E+00
910    an = a * term
911    do i = 1, 2
912      pn(i+4) = b * pn(i+2) - an * pn(i)
913    end do
914
915    if ( pn(6) /= 0.0E+00 ) then
916
917      rn = pn(5) / pn(6)
918      dif = abs ( gin - rn )
919!
920!  Absolute error tolerance satisfied?
921!
922      if ( dif <= acu ) then
923!
924!  Relative error tolerance satisfied?
925!
926        if ( dif <= acu * rn ) then
927          gamain = 1.0E+00 - factor * gin
928          exit
929        end if
930
931      end if
932
933      gin = rn
934
935    end if
936
937    do i = 1, 4
938      pn(i) = pn(i+2)
939    end do
940    if ( oflo <= abs ( pn(5) ) ) then
941
942      do i = 1, 4
943        pn(i) = pn(i) / oflo
944      end do
945
946    end if
947
948  end do
949
950  END FUNCTION gamain
951
952   !!======================================================================
953END MODULE p4zpoc
Note: See TracBrowser for help on using the repository browser.