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.
p4zrem.F90 in branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/CNRS/dev_r6270_PISCES_QUOTA/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90 @ 6841

Last change on this file since 6841 was 6841, checked in by aumont, 8 years ago

Various bug fixes + explicit gamma function for lability

File size: 16.0 KB
Line 
1MODULE p4zrem
2   !!======================================================================
3   !!                         ***  MODULE p4zrem  ***
4   !! TOP :   PISCES Compute remineralization/dissolution of organic compounds
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 reorganization
10   !!----------------------------------------------------------------------
11#if defined key_pisces
12   !!----------------------------------------------------------------------
13   !!   'key_top'       and                                      TOP models
14   !!   'key_pisces'                                       PISCES bio-model
15   !!----------------------------------------------------------------------
16   !!   p4z_rem       :  Compute remineralization/dissolution of organic compounds
17   !!   p4z_rem_init  :  Initialisation of parameters for remineralisation
18   !!   p4z_rem_alloc :  Allocate remineralisation variables
19   !!----------------------------------------------------------------------
20   USE oce_trc         !  shared variables between ocean and passive tracers
21   USE trc             !  passive tracers common variables
22   USE sms_pisces      !  PISCES Source Minus Sink variables
23   USE p4zopt          !  optical model
24   USE p4zche          !  chemical model
25   USE p4zlim          ! Phytoplankton limitation factors
26   USE p4zprod         !  Growth rate of the 2 phyto groups
27   USE prtctl_trc      !  print control for debugging
28   USE iom             !  I/O manager
29
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   p4z_rem         ! called in p4zbio.F90
35   PUBLIC   p4z_rem_init    ! called in trcsms_pisces.F90
36   PUBLIC   p4z_rem_alloc
37
38   !! * Shared module variables
39   REAL(wp), PUBLIC ::  xremik     !: remineralisation rate of DOC
40   REAL(wp), PUBLIC ::  nitrif     !: NH4 nitrification rate
41   REAL(wp), PUBLIC ::  xsirem     !: remineralisation rate of BSi
42   REAL(wp), PUBLIC ::  xsiremlab  !: fast remineralisation rate of BSi
43   REAL(wp), PUBLIC ::  xsilab     !: fraction of labile biogenic silica
44   REAL(wp), PUBLIC ::  oxymin     !: halk saturation constant for anoxia
45
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitr     !: denitrification array
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   denitnh4   !: -    -    -    -   -
48
49
50   !!* Substitution
51#  include "top_substitute.h90"
52   !!----------------------------------------------------------------------
53   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
54   !! $Id: p4zrem.F90 3160 2011-11-20 14:27:18Z cetlod $
55   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
56   !!----------------------------------------------------------------------
57CONTAINS
58
59   SUBROUTINE p4z_rem( kt, jnt )
60      !!---------------------------------------------------------------------
61      !!                     ***  ROUTINE p4z_rem  ***
62      !!
63      !! ** Purpose :   Compute remineralization/scavenging of organic compounds
64      !!
65      !! ** Method  : - ???
66      !!---------------------------------------------------------------------
67      !
68      INTEGER, INTENT(in) ::   kt, jnt ! ocean time step
69      !
70      INTEGER  ::   ji, jj, jk
71      REAL(wp) ::   zremik, zsiremin 
72      REAL(wp) ::   zsatur, zsatur2, znusil, znusil2, zdep, zdepmin, zfactdep
73      REAL(wp) ::   zbactfer, zolimit
74      REAL(wp) ::   zosil, ztem
75      REAL(wp) ::   zonitr, zstep, zrfact2
76      CHARACTER (len=25) :: charout
77      REAL(wp), POINTER, DIMENSION(:,:  ) :: ztempbac
78      REAL(wp), POINTER, DIMENSION(:,:,:) :: zdepbac, zolimi, zdepprod
79      !!---------------------------------------------------------------------
80      !
81      IF( nn_timing == 1 )  CALL timing_start('p4z_rem')
82      !
83      ! Allocate temporary workspace
84      CALL wrk_alloc( jpi, jpj,      ztempbac )
85      CALL wrk_alloc( jpi, jpj, jpk, zdepbac, zdepprod, zolimi )
86
87      ! Initialization of local variables
88      ! ---------------------------------
89
90      ! Initialisation of temprary arrys
91      zdepprod(:,:,:) = 1._wp
92      ztempbac(:,:)   = 0._wp
93
94      ! Computation of the mean phytoplankton concentration as
95      ! a crude estimate of the bacterial biomass
96      ! this parameterization has been deduced from a model version
97      ! that was modeling explicitely bacteria
98      ! -------------------------------------------------------
99      DO jk = 1, jpkm1
100         DO jj = 1, jpj
101            DO ji = 1, jpi
102               zdep = MAX( hmld(ji,jj), heup(ji,jj) )
103               IF( fsdept(ji,jj,jk) < zdep ) THEN
104                  zdepbac(ji,jj,jk) = MIN( 0.7 * ( trb(ji,jj,jk,jpzoo) + 2.* trb(ji,jj,jk,jpmes) ), 4.e-6 )
105                  ztempbac(ji,jj)   = zdepbac(ji,jj,jk)
106               ELSE
107                  zdepmin = MIN( 1., zdep / fsdept(ji,jj,jk) )
108                  zdepbac (ji,jj,jk) = zdepmin**0.683 * ztempbac(ji,jj)
109                  zdepprod(ji,jj,jk) = zdepmin**0.273
110               ENDIF
111            END DO
112         END DO
113      END DO
114
115      DO jk = 1, jpkm1
116         DO jj = 1, jpj
117            DO ji = 1, jpi
118               ! denitrification factor computed from O2 levels
119               nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - trb(ji,jj,jk,jpoxy) )    &
120                  &                                / ( oxymin + trb(ji,jj,jk,jpoxy) )  )
121               nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) )
122            END DO
123         END DO
124      END DO
125
126      DO jk = 1, jpkm1
127         DO jj = 1, jpj
128            DO ji = 1, jpi
129               zstep   = xstep
130# if defined key_degrad
131               zstep = zstep * facvol(ji,jj,jk)
132# endif
133               ! DOC ammonification. Depends on depth, phytoplankton biomass
134               ! and a limitation term which is supposed to be a parameterization
135               !     of the bacterial activity.
136               zremik = xremik * zstep / 1.e-6 * xlimbac(ji,jj,jk) * zdepbac(ji,jj,jk) 
137               zremik = MAX( zremik, 2.74e-4 * xstep )
138               ! Ammonification in oxic waters with oxygen consumption
139               ! -----------------------------------------------------
140               zolimit = zremik * ( 1.- nitrfac(ji,jj,jk) ) * trb(ji,jj,jk,jpdoc) 
141               zolimi(ji,jj,jk) = MIN( ( trb(ji,jj,jk,jpoxy) - rtrn ) / o2ut, zolimit ) 
142               ! Ammonification in suboxic waters with denitrification
143               ! -------------------------------------------------------
144               denitr(ji,jj,jk)  = MIN(  ( trb(ji,jj,jk,jpno3) - rtrn ) / rdenit,   &
145                  &                     zremik * nitrfac(ji,jj,jk) * trb(ji,jj,jk,jpdoc)  )
146               !
147               zolimi (ji,jj,jk) = MAX( 0.e0, zolimi (ji,jj,jk) )
148               denitr (ji,jj,jk) = MAX( 0.e0, denitr (ji,jj,jk) )
149               !
150            END DO
151         END DO
152      END DO
153
154
155      DO jk = 1, jpkm1
156         DO jj = 1, jpj
157            DO ji = 1, jpi
158               zstep   = xstep
159# if defined key_degrad
160               zstep = zstep * facvol(ji,jj,jk)
161# endif
162               ! NH4 nitrification to NO3. Ceased for oxygen concentrations
163               ! below 2 umol/L. Inhibited at strong light
164               ! ----------------------------------------------------------
165               zonitr  = nitrif * zstep * trb(ji,jj,jk,jpnh4) * ( 1.- nitrfac(ji,jj,jk) )  &
166               &         / ( 1.+ emoy(ji,jj,jk) ) * ( 1. + fr_i(ji,jj) * emoy(ji,jj,jk) )
167               denitnh4(ji,jj,jk) = nitrif * zstep * trb(ji,jj,jk,jpnh4) * nitrfac(ji,jj,jk) 
168               ! Update of the tracers trends
169               ! ----------------------------
170               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) - zonitr - denitnh4(ji,jj,jk)
171               tra(ji,jj,jk,jpno3) = tra(ji,jj,jk,jpno3) + zonitr - rdenita * denitnh4(ji,jj,jk)
172               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) - o2nit * zonitr
173               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) - 2 * rno3 * zonitr + rno3 * ( rdenita - 1. ) * denitnh4(ji,jj,jk)
174            END DO
175         END DO
176      END DO
177
178       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
179         WRITE(charout, FMT="('rem1')")
180         CALL prt_ctl_trc_info(charout)
181         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
182       ENDIF
183
184      DO jk = 1, jpkm1
185         DO jj = 1, jpj
186            DO ji = 1, jpi
187
188               ! Bacterial uptake of iron. No iron is available in DOC. So
189               ! Bacteries are obliged to take up iron from the water. Some
190               ! studies (especially at Papa) have shown this uptake to be significant
191               ! ----------------------------------------------------------
192               zbactfer = 10.e-6 *  rfact2 * prmax(ji,jj,jk) * xlimbacl(ji,jj,jk)             &
193                  &              * trb(ji,jj,jk,jpfer) / ( 2.5E-10 + trb(ji,jj,jk,jpfer) )    &
194                  &              * zdepprod(ji,jj,jk) * zdepbac(ji,jj,jk)
195#if defined key_kriest
196               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zbactfer*0.05
197               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zbactfer*0.05
198#else
199               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) - zbactfer*0.16
200               tra(ji,jj,jk,jpsfe) = tra(ji,jj,jk,jpsfe) + zbactfer*0.12
201               tra(ji,jj,jk,jpbfe) = tra(ji,jj,jk,jpbfe) + zbactfer*0.04
202#endif
203            END DO
204         END DO
205      END DO
206
207       IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
208         WRITE(charout, FMT="('rem2')")
209         CALL prt_ctl_trc_info(charout)
210         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
211       ENDIF
212
213      DO jk = 1, jpkm1
214         DO jj = 1, jpj
215            DO ji = 1, jpi
216               zstep   = xstep
217# if defined key_degrad
218               zstep = zstep * facvol(ji,jj,jk)
219# endif
220               ! Remineralization rate of BSi depedant on T and saturation
221               ! ---------------------------------------------------------
222               zsatur   = ( sio3eq(ji,jj,jk) - trb(ji,jj,jk,jpsil) ) / ( sio3eq(ji,jj,jk) + rtrn )
223               zsatur   = MAX( rtrn, zsatur )
224               zsatur2  = ( 1. + tsn(ji,jj,jk,jp_tem) / 400.)**37
225               znusil   = 0.225  * ( 1. + tsn(ji,jj,jk,jp_tem) / 15.) * zsatur + 0.775 * zsatur2 * zsatur**9.25
226               znusil2  = 0.225  * ( 1. + tsn(ji,jj,1,jp_tem) / 15.) + 0.775 * zsatur2
227
228               ! Two classes of BSi are considered : a labile fraction and
229               ! a more refractory one. The ratio between both fractions is
230               ! constant and specified in the namelist.
231               ! ----------------------------------------------------------
232               zdep     = MAX( hmld(ji,jj), heup_01(ji,jj) ) 
233               zdep     = MAX( 0., fsdept(ji,jj,jk) - zdep )
234               ztem     = MAX( tsn(ji,jj,1,jp_tem), 0. )
235               zfactdep = xsilab * EXP(-( xsiremlab - xsirem ) * znusil2 * zdep / wsbio2 ) * ztem / ( ztem + 10. )
236               zsiremin = ( xsiremlab * zfactdep + xsirem * ( 1. - zfactdep ) ) * zstep * znusil
237               zosil    = zsiremin * trb(ji,jj,jk,jpgsi)
238               !
239               tra(ji,jj,jk,jpgsi) = tra(ji,jj,jk,jpgsi) - zosil
240               tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) + zosil
241               !
242            END DO
243         END DO
244      END DO
245
246      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
247         WRITE(charout, FMT="('rem3')")
248         CALL prt_ctl_trc_info(charout)
249         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
250       ENDIF
251
252      ! Update the arrays TRA which contain the biological sources and sinks
253      ! --------------------------------------------------------------------
254
255      DO jk = 1, jpkm1
256         tra(:,:,jk,jppo4) = tra(:,:,jk,jppo4) + zolimi (:,:,jk) + denitr(:,:,jk)
257         tra(:,:,jk,jpnh4) = tra(:,:,jk,jpnh4) + zolimi (:,:,jk) + denitr(:,:,jk)
258         tra(:,:,jk,jpno3) = tra(:,:,jk,jpno3) - denitr (:,:,jk) * rdenit
259         tra(:,:,jk,jpdoc) = tra(:,:,jk,jpdoc) - zolimi (:,:,jk) - denitr(:,:,jk)
260         tra(:,:,jk,jpoxy) = tra(:,:,jk,jpoxy) - zolimi (:,:,jk) * o2ut
261         tra(:,:,jk,jpdic) = tra(:,:,jk,jpdic) + zolimi (:,:,jk) + denitr(:,:,jk)
262         tra(:,:,jk,jptal) = tra(:,:,jk,jptal) + rno3 * ( zolimi(:,:,jk) + ( rdenit + 1.) * denitr(:,:,jk) )
263      END DO
264
265      IF( ln_diatrc .AND. lk_iomput .AND. jnt == nrdttrc ) THEN
266          zrfact2 = 1.e3 * rfact2r
267          CALL iom_put( "REMIN" , zolimi(:,:,:) * tmask(:,:,:) * zrfact2 )  ! Remineralisation rate
268          CALL iom_put( "DENIT" , denitr(:,:,:) * rdenit * rno3 * tmask(:,:,:) * zrfact2  )  ! Denitrification
269      ENDIF
270
271      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
272         WRITE(charout, FMT="('rem4')")
273         CALL prt_ctl_trc_info(charout)
274         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
275      ENDIF
276      !
277      CALL wrk_dealloc( jpi, jpj,      ztempbac )
278      CALL wrk_dealloc( jpi, jpj, jpk, zdepbac, zdepprod, zolimi )
279      !
280      IF( nn_timing == 1 )  CALL timing_stop('p4z_rem')
281      !
282   END SUBROUTINE p4z_rem
283
284
285   SUBROUTINE p4z_rem_init
286      !!----------------------------------------------------------------------
287      !!                  ***  ROUTINE p4z_rem_init  ***
288      !!
289      !! ** Purpose :   Initialization of remineralization parameters
290      !!
291      !! ** Method  :   Read the nampisrem namelist and check the parameters
292      !!      called at the first timestep
293      !!
294      !! ** input   :   Namelist nampisrem
295      !!
296      !!----------------------------------------------------------------------
297      NAMELIST/nampisrem/ xremik, nitrif, xsirem, xsiremlab, xsilab,   &
298      &                   oxymin
299      INTEGER :: ios                 ! Local integer output status for namelist read
300
301      REWIND( numnatp_ref )              ! Namelist nampisrem in reference namelist : Pisces remineralization
302      READ  ( numnatp_ref, nampisrem, IOSTAT = ios, ERR = 901)
303901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisrem in reference namelist', lwp )
304
305      REWIND( numnatp_cfg )              ! Namelist nampisrem in configuration namelist : Pisces remineralization
306      READ  ( numnatp_cfg, nampisrem, IOSTAT = ios, ERR = 902 )
307902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisrem in configuration namelist', lwp )
308      IF(lwm) WRITE ( numonp, nampisrem )
309
310      IF(lwp) THEN                         ! control print
311         WRITE(numout,*) ' '
312         WRITE(numout,*) ' Namelist parameters for remineralization, nampisrem'
313         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
314         WRITE(numout,*) '    remineralization rate of DOC              xremik    =', xremik
315         WRITE(numout,*) '    remineralization rate of Si               xsirem    =', xsirem
316         WRITE(numout,*) '    fast remineralization rate of Si          xsiremlab =', xsiremlab
317         WRITE(numout,*) '    fraction of labile biogenic silica        xsilab    =', xsilab
318         WRITE(numout,*) '    NH4 nitrification rate                    nitrif    =', nitrif
319         WRITE(numout,*) '    halk saturation constant for anoxia       oxymin    =', oxymin
320      ENDIF
321      !
322      nitrfac (:,:,:) = 0._wp
323      denitr  (:,:,:) = 0._wp
324      denitnh4(:,:,:) = 0._wp
325
326   END SUBROUTINE p4z_rem_init
327
328
329   INTEGER FUNCTION p4z_rem_alloc()
330      !!----------------------------------------------------------------------
331      !!                     ***  ROUTINE p4z_rem_alloc  ***
332      !!----------------------------------------------------------------------
333      ALLOCATE( denitr(jpi,jpj,jpk), denitnh4(jpi,jpj,jpk), STAT=p4z_rem_alloc )
334      !
335      IF( p4z_rem_alloc /= 0 )   CALL ctl_warn('p4z_rem_alloc: failed to allocate arrays')
336      !
337   END FUNCTION p4z_rem_alloc
338
339#else
340   !!======================================================================
341   !!  Dummy module :                                   No PISCES bio-model
342   !!======================================================================
343CONTAINS
344   SUBROUTINE p4z_rem                    ! Empty routine
345   END SUBROUTINE p4z_rem
346#endif 
347
348   !!======================================================================
349END MODULE p4zrem
Note: See TracBrowser for help on using the repository browser.