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

source: trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zpoc.F90 @ 7698

Last change on this file since 7698 was 7698, checked in by mocavero, 7 years ago

update trunk with OpenMP parallelization

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