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

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90 @ 7398

Last change on this file since 7398 was 7398, checked in by cbricaud, 7 years ago

coarsening branch: first implementation of coarsening in PISCES

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