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

source: NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsed.F90 @ 10115

Last change on this file since 10115 was 10115, checked in by cbricaud, 6 years ago

phase 3.6 coarsening branch with nemo_3.6_rev9192

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