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

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

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

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