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

source: trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90 @ 4641

Last change on this file since 4641 was 4624, checked in by acc, 10 years ago

#1305. Fix slow start-up problems on some systems by introducing and using lwm logical to restrict output of merged namelists to the first (or only) processor. lwm is true only on the first processor regardless of ln_ctl. Small changes to all flavours of nemogcm.F90 are also required to write namctl and namcfg after the call to mynode which now opens output.namelist.dyn and writes nammpp.

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