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.
p4zsed.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/p4zsed.F90 @ 8003

Last change on this file since 8003 was 8003, checked in by aumont, 7 years ago

modification in the code to remove unnecessary parts such as kriest and non iomput options

  • Property svn:keywords set to Id
File size: 21.4 KB
Line 
1MODULE p4zsed
2   !!======================================================================
3   !!                         ***  MODULE p4sed  ***
4   !! TOP :   PISCES Compute loss of organic matter in the sediments
5   !!======================================================================
6   !! History :   1.0  !  2004-03 (O. Aumont) Original code
7   !!             2.0  !  2007-12 (C. Ethe, G. Madec)  F90
8   !!             3.4  !  2011-06 (C. Ethe) USE of fldread
9   !!             3.5  !  2012-07 (O. Aumont) improvment of river input of nutrients
10   !!----------------------------------------------------------------------
11#if defined key_pisces
12   !!----------------------------------------------------------------------
13   !!   'key_pisces'                                       PISCES bio-model
14   !!----------------------------------------------------------------------
15   !!   p4z_sed        :  Compute loss of organic matter in the sediments
16   !!----------------------------------------------------------------------
17   USE oce_trc         !  shared variables between ocean and passive tracers
18   USE trc             !  passive tracers common variables
19   USE sms_pisces      !  PISCES Source Minus Sink variables
20   USE p4zsink         !  vertical flux of particulate matter due to sinking
21   USE p4zopt          !  optical model
22   USE p4zlim          !  Co-limitations of differents nutrients
23   USE p4zsbc          !  External source of nutrients
24   USE p4zint          !  interpolation and computation of various fields
25   USE iom             !  I/O manager
26   USE prtctl_trc      !  print control for debugging
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   p4z_sed 
32   PUBLIC   p4z_sed_alloc
33 
34
35   !! * Module variables
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: nitrpot    !: Nitrogen fixation
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:  ) :: sdenit     !: Nitrate reduction in the sediments
38   REAL(wp) :: r1_rday                  !: inverse of rday
39
40   !!* Substitution
41#  include "top_substitute.h90"
42   !!----------------------------------------------------------------------
43   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
44   !! $Id$
45   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE p4z_sed( kt, knt )
50      !!---------------------------------------------------------------------
51      !!                     ***  ROUTINE p4z_sed  ***
52      !!
53      !! ** Purpose :   Compute loss of organic matter in the sediments. This
54      !!              is by no way a sediment model. The loss is simply
55      !!              computed to balance the inout from rivers and dust
56      !!
57      !! ** Method  : - ???
58      !!---------------------------------------------------------------------
59      !
60      INTEGER, INTENT(in) ::   kt, knt ! ocean time step
61      INTEGER  ::   ji, jj, jk, ikt
62#if ! defined key_sed
63      REAL(wp) ::   zsumsedsi, zsumsedpo4, zsumsedcal
64      REAL(wp) ::   zrivalk, zrivsil, zrivno3
65#endif
66      REAL(wp) ::  zwflux, zfminus, zfplus
67      REAL(wp) ::  zlim, zfact, zfactcal
68      REAL(wp) ::  zo2, zno3, zflx, zpdenit, z1pdenit, zdenitt, zolimit
69      REAL(wp) ::  zsiloss, zcaloss, zws3, zws4, zwsc, zdep, zwstpoc
70      REAL(wp) ::  ztrfer, ztrpo4, zwdust, zlight
71      !
72      CHARACTER (len=25) :: charout
73      REAL(wp), POINTER, DIMENSION(:,:  ) :: zpdep, zsidep, zwork1, zwork2, zwork3
74      REAL(wp), POINTER, DIMENSION(:,:)   :: zsedcal, zsedsi, zsedc
75      REAL(wp), POINTER, DIMENSION(:,:  ) :: zdenit2d, zironice, zbureff
76      REAL(wp), POINTER, DIMENSION(:,:  ) :: zwsbio3, zwsbio4, zwscal
77      REAL(wp), POINTER, DIMENSION(:,:,:) :: zirondep, zsoufer
78#if defined key_ligand
79      REAL(wp) ::  zwssfep
80      REAL(wp), POINTER, DIMENSION(:,:  ) :: zwsfep
81#endif
82      !!---------------------------------------------------------------------
83      !
84      IF( nn_timing == 1 )  CALL timing_start('p4z_sed')
85      !
86      IF( kt == nittrc000 .AND. knt == 1 )   r1_rday  = 1. / rday
87      !
88      ! Allocate temporary workspace
89      CALL wrk_alloc( jpi, jpj, zdenit2d, zwork1, zwork2, zwork3, zbureff )
90      CALL wrk_alloc( jpi, jpj, zsedcal,  zsedsi, zsedc )
91      CALL wrk_alloc( jpi, jpj, zwsbio3, zwsbio4, zwscal )
92      CALL wrk_alloc( jpi, jpj, jpk, zsoufer )
93#if defined key_ligand
94      CALL wrk_alloc( jpi, jpj, zwsfep )
95#endif
96
97      zdenit2d(:,:) = 0.e0
98      zbureff (:,:) = 0.e0
99      zwork1  (:,:) = 0.e0
100      zwork2  (:,:) = 0.e0
101      zwork3  (:,:) = 0.e0
102      zsedsi   (:,:) = 0.e0
103      zsedcal  (:,:) = 0.e0
104      zsedc    (:,:) = 0.e0
105
106      ! Iron input/uptake due to sea ice : Crude parameterization based on Lancelot et al.
107      ! ----------------------------------------------------
108      IF( ln_ironice ) THEN 
109         !                                             
110         CALL wrk_alloc( jpi, jpj, zironice )
111         !                                             
112         DO jj = 1, jpj
113            DO ji = 1, jpi
114               zdep    = rfact2 / fse3t(ji,jj,1)
115               zwflux  = fmmflx(ji,jj) / 1000._wp
116               zfminus = MIN( 0._wp, -zwflux ) * trb(ji,jj,1,jpfer) * zdep
117               zfplus  = MAX( 0._wp, -zwflux ) * icefeinput * zdep
118               zironice(ji,jj) =  zfplus + zfminus
119            END DO
120         END DO
121         !
122         tra(:,:,1,jpfer) = tra(:,:,1,jpfer) + zironice(:,:) 
123         !
124         IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "Ironice" ) )   &
125            &   CALL iom_put( "Ironice", zironice(:,:) * 1.e+3 * rfact2r * fse3t(:,:,1) * tmask(:,:,1) ) ! iron flux from ice
126         !
127         CALL wrk_dealloc( jpi, jpj, zironice )
128         !                                             
129      ENDIF
130
131      ! Add the external input of nutrients from dust deposition
132      ! ----------------------------------------------------------
133      IF( ln_dust ) THEN
134         !                                             
135         CALL wrk_alloc( jpi, jpj,      zpdep, zsidep )
136         CALL wrk_alloc( jpi, jpj, jpk, zirondep      )
137         !                                              ! Iron and Si deposition at the surface
138         IF( ln_solub ) THEN
139            zirondep(:,:,1) = solub(:,:) * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 55.85 + 3.e-10 * r1_ryyss 
140         ELSE
141            zirondep(:,:,1) = dustsolub  * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 55.85 + 3.e-10 * r1_ryyss 
142         ENDIF
143         zsidep(:,:) = 8.8 * 0.075 * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 28.1 
144         zpdep (:,:) = 0.1 * 0.021 * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 31. / po4r 
145         !                                              ! Iron solubilization of particles in the water column
146         !                                              ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/j
147         zwdust = 0.03 * rday / ( wdust * 55.85 ) / ( 270. * rday )
148         DO jk = 2, jpkm1
149            zirondep(:,:,jk) = dust(:,:) * mfrac * zwdust * rfact2 * EXP( -fsdept(:,:,jk) / 540. )
150         END DO
151         !                                              ! Iron solubilization of particles in the water column
152         tra(:,:,1,jppo4) = tra(:,:,1,jppo4) + zpdep   (:,:)
153         tra(:,:,1,jpsil) = tra(:,:,1,jpsil) + zsidep  (:,:)
154         tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + zirondep(:,:,:) 
155         !
156         IF( lk_iomput ) THEN
157            IF( knt == nrdttrc ) THEN
158                IF( iom_use( "Irondep" ) )   &
159                &  CALL iom_put( "Irondep", zirondep(:,:,1) * 1.e+3 * rfact2r * fse3t(:,:,1) * tmask(:,:,1) ) ! surface downward dust depo of iron
160                IF( iom_use( "pdust" ) )   &
161                &  CALL iom_put( "pdust"  , dust(:,:) / ( wdust * rday )  * tmask(:,:,1) ) ! dust concentration at surface
162            ENDIF
163         ELSE                                   
164            IF( ln_diatrc )  &
165              &  trc2d(:,:,jp_pcs0_2d + 11) = zirondep(:,:,1) * 1.e+3 * rfact2r * fse3t(:,:,1) * tmask(:,:,1)
166         ENDIF
167         CALL wrk_dealloc( jpi, jpj,      zpdep, zsidep )
168         CALL wrk_dealloc( jpi, jpj, jpk, zirondep      )
169         !                                             
170      ENDIF
171     
172      ! Add the external input of nutrients from river
173      ! ----------------------------------------------------------
174      IF( ln_river ) THEN
175         DO jj = 1, jpj
176            DO ji = 1, jpi
177               DO jk = 1, nk_rnf(ji,jj)
178                  tra(ji,jj,jk,jppo4) = tra(ji,jj,jk,jppo4) +  rivdip(ji,jj) * rfact2
179                  tra(ji,jj,jk,jpno3) = tra(ji,jj,jk,jpno3) +  rivdin(ji,jj) * rfact2
180                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) +  rivdic(ji,jj) * 5.e-5 * rfact2
181                  tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) +  rivdsi(ji,jj) * rfact2
182                  tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) +  rivdic(ji,jj) * rfact2
183                  tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) +  ( rivalk(ji,jj) - rno3 * rivdin(ji,jj) ) * rfact2
184               ENDDO
185            ENDDO
186         ENDDO
187      ENDIF
188     
189      ! Add the external input of nutrients from nitrogen deposition
190      ! ----------------------------------------------------------
191      IF( ln_ndepo ) THEN
192         tra(:,:,1,jpno3) = tra(:,:,1,jpno3) + nitdep(:,:) * rfact2
193         tra(:,:,1,jptal) = tra(:,:,1,jptal) - rno3 * nitdep(:,:) * rfact2
194      ENDIF
195
196      ! Add the external input of iron from sediment mobilization
197      ! ------------------------------------------------------
198      IF( ln_ironsed ) THEN
199         tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + ironsed(:,:,:) * rfact2
200#if defined key_ligand
201         tra(:,:,:,jpfep) = tra(:,:,:,jpfep) + (ironsed(:,:,:) * fep_rats ) * rfact2
202#endif
203         !
204         IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "Ironsed" ) )   &
205            &   CALL iom_put( "Ironsed", ironsed(:,:,:) * 1.e+3 * tmask(:,:,:) ) ! iron inputs from sediments
206      ENDIF
207
208      ! Add the external input of iron from hydrothermal vents
209      ! ------------------------------------------------------
210      IF( ln_hydrofe ) THEN
211         tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + hydrofe(:,:,:) * rfact2
212#if defined key_ligand
213         tra(:,:,:,jpfep) = tra(:,:,:,jpfep) + ( hydrofe(:,:,:) * fep_rath ) * rfact2
214         tra(:,:,:,jplgw) = tra(:,:,:,jplgw) + ( hydrofe(:,:,:) * hydrolig ) * rfact2
215#endif
216         !
217         IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "HYDR" ) )   &
218            &   CALL iom_put( "HYDR", hydrofe(:,:,:) * 1.e+3 * tmask(:,:,:) ) ! hydrothermal iron input
219      ENDIF
220
221      ! OA: Warning, the following part is necessary, especially with Kriest
222      ! to avoid CFL problems above the sediments
223      ! --------------------------------------------------------------------
224      DO jj = 1, jpj
225         DO ji = 1, jpi
226            ikt  = mbkt(ji,jj)
227            zdep = fse3t(ji,jj,ikt) / xstep
228            zwsbio4(ji,jj) = MIN( 0.99 * zdep, wsbio4(ji,jj,ikt) )
229            zwscal (ji,jj) = MIN( 0.99 * zdep, wscal (ji,jj,ikt) )
230            zwsbio3(ji,jj) = MIN( 0.99 * zdep, wsbio3(ji,jj,ikt) )
231#if defined key_ligand
232            zwsfep(ji,jj)  = MIN( 0.99 * zdep, wsfep(ji,jj,ikt)  )
233#endif
234         END DO
235      END DO
236
237#if ! defined key_sed
238      ! Computation of the sediment denitrification proportion: The metamodel from midlleburg (2006) is being used
239      ! Computation of the fraction of organic matter that is permanently buried from Dunne's model
240      ! -------------------------------------------------------
241      DO jj = 1, jpj
242         DO ji = 1, jpi
243           IF( tmask(ji,jj,1) == 1 ) THEN
244              ikt = mbkt(ji,jj)
245              zflx = (  trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj)   &
246                &     + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) )  * 1E3 * 1E6 / 1E4
247              zflx  = LOG10( MAX( 1E-3, zflx ) )
248              zo2   = LOG10( MAX( 10. , trb(ji,jj,ikt,jpoxy) * 1E6 ) )
249              zno3  = LOG10( MAX( 1.  , trb(ji,jj,ikt,jpno3) * 1E6 * rno3 ) )
250              zdep  = LOG10( fsdepw(ji,jj,ikt+1) )
251              zdenit2d(ji,jj) = -2.2567 - 1.185 * zflx - 0.221 * zflx**2 - 0.3995 * zno3 * zo2 + 1.25 * zno3    &
252              &                + 0.4721 * zo2 - 0.0996 * zdep + 0.4256 * zflx * zo2
253              zdenit2d(ji,jj) = 10.0**( zdenit2d(ji,jj) )
254              !
255              zflx = (  trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj)   &
256                &     + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) ) * 1E6
257              zbureff(ji,jj) = 0.013 + 0.53 * zflx**2 / ( 7.0 + zflx )**2
258           ENDIF
259         END DO
260      END DO 
261
262      ! Loss of biogenic silicon, Caco3 organic carbon in the sediments.
263      ! First, the total loss is computed.
264      ! The factor for calcite comes from the alkalinity effect
265      ! -------------------------------------------------------------
266      DO jj = 1, jpj
267         DO ji = 1, jpi
268            IF( tmask(ji,jj,1) == 1 ) THEN
269               ikt = mbkt(ji,jj) 
270               zwork1(ji,jj) = trb(ji,jj,ikt,jpgsi) * zwsbio4(ji,jj)
271               zwork2(ji,jj) = trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj) + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) 
272               ! For calcite, burial efficiency is made a function of saturation
273               zfactcal      = MIN( excess(ji,jj,ikt), 0.2 )
274               zfactcal      = MIN( 1., 1.3 * ( 0.2 - zfactcal ) / ( 0.4 - zfactcal ) )
275               zwork3(ji,jj) = trb(ji,jj,ikt,jpcal) * zwscal(ji,jj) * 2.e0 * zfactcal
276            ENDIF
277         END DO
278      END DO
279      zsumsedsi  = glob_sum( zwork1(:,:) * e1e2t(:,:) ) * r1_rday
280      zsumsedpo4 = glob_sum( zwork2(:,:) * e1e2t(:,:) ) * r1_rday
281      zsumsedcal = glob_sum( zwork3(:,:) * e1e2t(:,:) ) * r1_rday
282#endif
283
284      ! This loss is scaled at each bottom grid cell for equilibrating the total budget of silica in the ocean.
285      ! Thus, the amount of silica lost in the sediments equal the supply at the surface (dust+rivers)
286      ! ------------------------------------------------------
287#if ! defined key_sed
288      zrivsil =  1._wp - ( sumdepsi + rivdsiinput * r1_ryyss ) / ( zsumsedsi + rtrn )
289#endif
290
291      DO jj = 1, jpj
292         DO ji = 1, jpi
293            ikt  = mbkt(ji,jj)
294            zdep = xstep / fse3t(ji,jj,ikt) 
295            zws4 = zwsbio4(ji,jj) * zdep
296            zwsc = zwscal (ji,jj) * zdep
297            zsiloss = trb(ji,jj,ikt,jpgsi) * zwsc
298            zcaloss = trb(ji,jj,ikt,jpcal) * zwsc
299            !
300            tra(ji,jj,ikt,jpgsi) = tra(ji,jj,ikt,jpgsi) - zsiloss
301            tra(ji,jj,ikt,jpcal) = tra(ji,jj,ikt,jpcal) - zcaloss
302#if ! defined key_sed
303            tra(ji,jj,ikt,jpsil) = tra(ji,jj,ikt,jpsil) + zsiloss * zrivsil 
304            zfactcal = MIN( excess(ji,jj,ikt), 0.2 )
305            zfactcal = MIN( 1., 1.3 * ( 0.2 - zfactcal ) / ( 0.4 - zfactcal ) )
306            zrivalk  =  1._wp - ( rivalkinput * r1_ryyss ) * zfactcal / ( zsumsedcal + rtrn )
307            tra(ji,jj,ikt,jptal) =  tra(ji,jj,ikt,jptal) + zcaloss * zrivalk * 2.0
308            tra(ji,jj,ikt,jpdic) =  tra(ji,jj,ikt,jpdic) + zcaloss * zrivalk
309            zsedcal(ji,jj) = (1.0 - zrivalk) * zcaloss / zdep
310            zsedsi (ji,jj) = (1.0 - zrivsil) * zsiloss / zdep
311#endif
312         END DO
313      END DO
314
315      DO jj = 1, jpj
316         DO ji = 1, jpi
317            ikt  = mbkt(ji,jj)
318            zdep = xstep / fse3t(ji,jj,ikt) 
319            zws4 = zwsbio4(ji,jj) * zdep
320            zws3 = zwsbio3(ji,jj) * zdep
321#if defined key_ligand
322            zwssfep = zwsfep(ji,jj) * zdep
323#endif
324            zrivno3 = 1. - zbureff(ji,jj)
325            tra(ji,jj,ikt,jpgoc) = tra(ji,jj,ikt,jpgoc) - trb(ji,jj,ikt,jpgoc) * zws4 
326            tra(ji,jj,ikt,jppoc) = tra(ji,jj,ikt,jppoc) - trb(ji,jj,ikt,jppoc) * zws3
327            tra(ji,jj,ikt,jpbfe) = tra(ji,jj,ikt,jpbfe) - trb(ji,jj,ikt,jpbfe) * zws4
328            tra(ji,jj,ikt,jpsfe) = tra(ji,jj,ikt,jpsfe) - trb(ji,jj,ikt,jpsfe) * zws3
329            zwstpoc              = trb(ji,jj,ikt,jpgoc) * zws4 + trb(ji,jj,ikt,jppoc) * zws3
330#   if defined key_ligand
331            tra(ji,jj,ikt,jpfep) = tra(ji,jj,ikt,jpfep) - trn(ji,jj,ikt,jpfep) * zwssfep
332#   endif
333
334#if ! defined key_sed
335            ! The 0.5 factor in zpdenit and zdenitt is to avoid negative NO3 concentration after both denitrification
336            ! in the sediments and just above the sediments. Not very clever, but simpliest option.
337            zpdenit  = MIN( 0.5 * ( trb(ji,jj,ikt,jpno3) - rtrn ) / rdenit, zdenit2d(ji,jj) * zwstpoc * zrivno3 )
338            z1pdenit = zwstpoc * zrivno3 - zpdenit
339            zolimit = MIN( ( trb(ji,jj,ikt,jpoxy) - rtrn ) / o2ut, z1pdenit * ( 1.- nitrfac(ji,jj,ikt) ) )
340            zdenitt = MIN(  0.5 * ( trb(ji,jj,ikt,jpno3) - rtrn ) / rdenit, z1pdenit * nitrfac(ji,jj,ikt) )
341            tra(ji,jj,ikt,jpdoc) = tra(ji,jj,ikt,jpdoc) + z1pdenit - zolimit - zdenitt
342            tra(ji,jj,ikt,jppo4) = tra(ji,jj,ikt,jppo4) + zpdenit + zolimit + zdenitt
343            tra(ji,jj,ikt,jpnh4) = tra(ji,jj,ikt,jpnh4) + zpdenit + zolimit + zdenitt
344            tra(ji,jj,ikt,jpno3) = tra(ji,jj,ikt,jpno3) - rdenit * (zpdenit + zdenitt)
345            tra(ji,jj,ikt,jpoxy) = tra(ji,jj,ikt,jpoxy) - zolimit * o2ut
346            tra(ji,jj,ikt,jptal) = tra(ji,jj,ikt,jptal) + rno3 * (zolimit + (1.+rdenit) * (zpdenit + zdenitt) )
347            tra(ji,jj,ikt,jpdic) = tra(ji,jj,ikt,jpdic) + zpdenit + zolimit + zdenitt
348            sdenit(ji,jj) = rdenit * zpdenit / zdep
349            zsedc(ji,jj)   = (1. - zrivno3) * zwstpoc / zdep
350#endif
351         END DO
352      END DO
353
354      ! Nitrogen fixation process
355      ! Small source iron from particulate inorganic iron
356      !-----------------------------------
357      DO jk = 1, jpkm1
358         DO jj = 1, jpj
359            DO ji = 1, jpi
360               !                      ! Potential nitrogen fixation dependant on temperature and iron
361               zlim = ( 1.- xnanono3(ji,jj,jk) - xnanonh4(ji,jj,jk) )
362               IF( zlim <= 0.2 )   zlim = 0.01
363               zfact = zlim * rfact2
364               ztrfer = biron(ji,jj,jk)       / ( concfediaz + biron(ji,jj,jk)       )
365               ztrpo4 = trb  (ji,jj,jk,jppo4) / ( concnnh4   + trb  (ji,jj,jk,jppo4) ) 
366               zlight =  ( 1.- EXP( -etot_ndcy(ji,jj,jk) / diazolight ) ) 
367               nitrpot(ji,jj,jk) =  MAX( 0.e0, ( 0.6 * tgfunc(ji,jj,jk) - 2.15 ) * r1_rday )   &
368                 &         *  zfact * MIN( ztrfer, ztrpo4 ) * zlight * (1. - fr_i(ji,jj))
369               zsoufer(ji,jj,jk) = zlight * 2E-11 / (2E-11 + biron(ji,jj,jk))
370            END DO
371         END DO
372      END DO
373
374      ! Nitrogen change due to nitrogen fixation
375      ! ----------------------------------------
376      DO jk = 1, jpkm1
377         DO jj = 1, jpj
378            DO ji = 1, jpi
379               zfact = nitrpot(ji,jj,jk) * nitrfix
380               tra(ji,jj,jk,jpnh4) = tra(ji,jj,jk,jpnh4) +             zfact
381               tra(ji,jj,jk,jptal) = tra(ji,jj,jk,jptal) + rno3      * zfact
382               tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) + o2nit     * zfact 
383               tra(ji,jj,jk,jppo4) = tra(ji,jj,jk,jppo4) + concdnh4 / ( concdnh4 + trb(ji,jj,jk,jppo4) ) &
384               &                     * 0.002 * trb(ji,jj,jk,jpdoc) * xstep
385               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + 0.002 * 4E-10 * zsoufer(ji,jj,jk) * xstep
386           END DO
387         END DO
388      END DO
389
390      IF( lk_iomput ) THEN
391         IF( knt == nrdttrc ) THEN
392            zfact = 1.e+3 * rfact2r * rno3  !  conversion from molC/l/kt  to molN/m3/s
393            IF( iom_use("Nfix"   ) ) CALL iom_put( "Nfix", nitrpot(:,:,:) * nitrfix * zfact * tmask(:,:,:) )  ! nitrogen fixation
394            IF( iom_use("INTNFIX") ) THEN   ! nitrogen fixation rate in ocean ( vertically integrated )
395               zwork1(:,:) = 0.
396               DO jk = 1, jpkm1
397                 zwork1(:,:) = zwork1(:,:) + nitrpot(:,:,jk) * nitrfix * zfact * fse3t(:,:,jk) * tmask(:,:,jk)
398               ENDDO
399               CALL iom_put( "INTNFIX" , zwork1 ) 
400            ENDIF
401            IF( iom_use("SedCal" ) ) CALL iom_put( "SedCal", zsedcal(:,:) * 1.e+3 )
402            IF( iom_use("SedSi" ) )  CALL iom_put( "SedSi",  zsedsi (:,:) * 1.e+3 )
403            IF( iom_use("SedC" ) )   CALL iom_put( "SedC",   zsedc  (:,:) * 1.e+3 )
404            IF( iom_use("Sdenit" ) ) CALL iom_put( "Sdenit", sdenit (:,:) * 1.e+3 * rno3 )
405         ENDIF
406      ENDIF
407      !
408      IF(ln_ctl) THEN  ! print mean trends (USEd for debugging)
409         WRITE(charout, fmt="('sed ')")
410         CALL prt_ctl_trc_info(charout)
411         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
412      ENDIF
413      !
414      CALL wrk_dealloc( jpi, jpj, zdenit2d, zwork1, zwork2, zwork3, zbureff )
415      CALL wrk_dealloc( jpi, jpj, zsedcal , zsedsi, zsedc )
416      CALL wrk_dealloc( jpi, jpj, zwsbio3, zwsbio4, zwscal )
417      CALL wrk_dealloc( jpi, jpj, jpk, zsoufer )
418#if defined key_ligand
419      CALL wrk_dealloc( jpi, jpj, zwsfep )
420#endif
421      !
422      IF( nn_timing == 1 )  CALL timing_stop('p4z_sed')
423      !
424 9100  FORMAT(i8,3f10.5)
425      !
426   END SUBROUTINE p4z_sed
427
428
429   INTEGER FUNCTION p4z_sed_alloc()
430      !!----------------------------------------------------------------------
431      !!                     ***  ROUTINE p4z_sed_alloc  ***
432      !!----------------------------------------------------------------------
433      ALLOCATE( nitrpot(jpi,jpj,jpk), sdenit(jpi,jpj), STAT=p4z_sed_alloc )
434      !
435      IF( p4z_sed_alloc /= 0 )   CALL ctl_warn('p4z_sed_alloc: failed to allocate arrays')
436      !
437   END FUNCTION p4z_sed_alloc
438
439
440#else
441   !!======================================================================
442   !!  Dummy module :                                   No PISCES bio-model
443   !!======================================================================
444CONTAINS
445   SUBROUTINE p4z_sed                         ! Empty routine
446   END SUBROUTINE p4z_sed
447#endif 
448
449   !!======================================================================
450END MODULE p4zsed
Note: See TracBrowser for help on using the repository browser.