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

source: branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90 @ 7068

Last change on this file since 7068 was 7068, checked in by cetlod, 8 years ago

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

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