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.
p4zsms.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/p4zsms.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

File size: 25.1 KB
Line 
1MODULE p4zsms
2   !!======================================================================
3   !!                         ***  MODULE p4zsms  ***
4   !! TOP :   PISCES Source Minus Sink manager
5   !!======================================================================
6   !! History :   1.0  !  2004-03 (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!----------------------------------------------------------------------
9#if defined key_pisces
10   !!----------------------------------------------------------------------
11   !!   'key_pisces'                                       PISCES bio-model
12   !!----------------------------------------------------------------------
13   !!   p4zsms         :  Time loop of passive tracers sms
14   !!----------------------------------------------------------------------
15   USE oce_trc         !  shared variables between ocean and passive tracers
16   USE trc             !  passive tracers common variables
17   USE trcdta
18   USE sms_pisces      !  PISCES Source Minus Sink variables
19   USE p4zbio          !  Biological model
20   USE p4zche          !  Chemical model
21   USE p4zlys          !  Calcite saturation
22   USE p4zflx          !  Gas exchange
23   USE p4zsbc          !  External source of nutrients
24   USE p4zsed          !  Sedimentation
25   USE p4zint          !  time interpolation
26   USE p4zrem          !  remineralisation
27   USE iom             !  I/O manager
28   USE trd_oce         !  Ocean trends variables
29   USE trdtrc          !  TOP trends variables
30   USE sedmodel        !  Sediment model
31   USE prtctl_trc      !  print control for debugging
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   p4z_sms_init   ! called in p4zsms.F90
37   PUBLIC   p4z_sms        ! called in p4zsms.F90
38
39   REAL(wp) :: alkbudget, no3budget, silbudget, ferbudget, po4budget
40   REAL(wp) :: xfact1, xfact2, xfact3
41   INTEGER ::  numco2, numnut, numnit  !: logical unit for co2 budget
42
43   !!* Array used to indicate negative tracer values
44   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     !: ???
45
46
47   !! * Substitutions
48#  include "top_substitute.h90"
49   !!----------------------------------------------------------------------
50   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
51   !! $Id: p4zsms.F90 3320 2012-03-05 16:37:52Z cetlod $
52   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
53   !!----------------------------------------------------------------------
54
55CONTAINS
56
57   SUBROUTINE p4z_sms( kt )
58      !!---------------------------------------------------------------------
59      !!                     ***  ROUTINE p4z_sms  ***
60      !!
61      !! ** Purpose :   Managment of the call to Biological sources and sinks
62      !!              routines of PISCES bio-model
63      !!
64      !! ** Method  : - at each new day ...
65      !!              - several calls of bio and sed ???
66      !!              - ...
67      !!---------------------------------------------------------------------
68      !
69      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
70      !!
71      INTEGER ::   ji, jj, jk, jnt, jn, jl
72      REAL(wp) ::  ztra
73      CHARACTER (len=25) :: charout
74      !!---------------------------------------------------------------------
75      !
76      IF( nn_timing == 1 )  CALL timing_start('p4z_sms')
77      !
78      IF( kt == nittrc000 ) THEN
79        !
80        ALLOCATE( xnegtr(jpi,jpj,jpk) )
81        !
82        CALL p4z_che                              ! initialize the chemical constants
83        !
84        IF( .NOT. ln_rsttr ) THEN  ;   CALL ahini_for_at(hi)   !  set PH at kt=nit000
85        ELSE                       ;   CALL p4z_rst( nittrc000, 'READ' )  !* read or initialize all required fields
86        ENDIF
87        !
88      ENDIF
89      !
90      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt )      ! Relaxation of some tracers
91      !
92      !                                                                    !   set time step size (Euler/Leapfrog)
93      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN   ;    rfact = rdttrc(1)     !  at nittrc000
94      ELSEIF( kt <= nittrc000 + nn_dttrc )                          THEN   ;    rfact = 2. * rdttrc(1)   ! at nittrc000 or nittrc000+nn_dttrc (Leapfrog)
95      ENDIF
96      !
97      IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + nn_dttrc ) ) THEN
98         rfactr  = 1. / rfact
99         rfact2  = rfact / FLOAT( nrdttrc )
100         rfact2r = 1. / rfact2
101         xstep = rfact2 / rday         ! Time step duration for biology
102         IF(lwp) WRITE(numout,*) 
103         IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdttra(1)
104         IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2
105         IF(lwp) WRITE(numout,*)
106      ENDIF
107
108      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN
109         DO jn = jp_pcs0, jp_pcs1              !   SMS on tracer without Asselin time-filter
110            trb(:,:,:,jn) = trn(:,:,:,jn)
111         END DO
112      ENDIF
113      !
114      IF( ndayflxtr /= nday_year ) THEN      ! New days
115         !
116         ndayflxtr = nday_year
117
118         IF(lwp) write(numout,*)
119         IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year
120         IF(lwp) write(numout,*) '~~~~~~'
121
122         CALL p4z_che              ! computation of chemical constants
123         CALL p4z_int( kt )        ! computation of various rates for biogeochemistry
124         !
125      ENDIF
126
127      IF( ll_sbc ) CALL p4z_sbc( kt )   ! external sources of nutrients
128
129      DO jnt = 1, nrdttrc          ! Potential time splitting if requested
130         !
131         CALL p4z_bio( kt, jnt )   ! Biology
132         CALL p4z_lys( kt, jnt )   ! Compute CaCO3 saturation
133         CALL p4z_flx( kt, jnt )   ! Compute surface fluxes
134         CALL p4z_sed( kt, jnt )   ! Sedimentation
135         !
136         xnegtr(:,:,:) = 1.e0
137         DO jn = jp_pcs0, jp_pcs1
138            DO jk = 1, jpk
139               DO jj = 1, jpj
140                  DO ji = 1, jpi
141                     IF( ( trb(ji,jj,jk,jn) + tra(ji,jj,jk,jn) ) < 0.e0 ) THEN
142                        ztra             = ABS( trb(ji,jj,jk,jn) ) / ( ABS( tra(ji,jj,jk,jn) ) + rtrn )
143                        xnegtr(ji,jj,jk) = MIN( xnegtr(ji,jj,jk),  ztra )
144                     ENDIF
145                 END DO
146               END DO
147            END DO
148         END DO
149         !                                ! where at least 1 tracer concentration becomes negative
150         !                                !
151         DO jn = jp_pcs0, jp_pcs1
152           trb(:,:,:,jn) = trb(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn)
153         END DO
154        !
155         DO jn = jp_pcs0, jp_pcs1
156            tra(:,:,:,jn) = 0._wp
157         END DO
158         !
159         IF( ln_top_euler ) THEN
160            DO jn = jp_pcs0, jp_pcs1
161               trn(:,:,:,jn) = trb(:,:,:,jn)
162            END DO
163         ENDIF
164      END DO
165      !
166      !
167      IF( l_trdtrc ) THEN
168         DO jn = jp_pcs0, jp_pcs1
169           CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt )   ! save trends
170         END DO
171      END IF
172      !
173      IF( lk_sed ) THEN 
174         !
175         CALL sed_model( kt )     !  Main program of Sediment model
176         !
177         DO jn = jp_pcs0, jp_pcs1
178           CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. )
179         END DO
180         !
181      ENDIF
182      !
183      IF( lrst_trc )  CALL p4z_rst( kt, 'WRITE' )  !* Write PISCES informations in restart file
184      !
185
186      IF( lk_iomput .OR. ln_check_mass )  CALL p4z_chk_mass( kt ) ! Mass conservation checking
187
188      IF ( lwm .AND. kt == nittrc000 ) CALL FLUSH    ( numonp )     ! flush output namelist PISCES
189      IF( nn_timing == 1 )  CALL timing_stop('p4z_sms')
190      !
191      !
192   END SUBROUTINE p4z_sms
193
194   SUBROUTINE p4z_sms_init
195      !!----------------------------------------------------------------------
196      !!                     ***  p4z_sms_init  *** 
197      !!
198      !! ** Purpose :   read PISCES namelist
199      !!
200      !! ** input   :   file 'namelist.trc.s' containing the following
201      !!             namelist: natext, natbio, natsms
202      !!----------------------------------------------------------------------
203#if defined key_ligand
204      NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2, wsbio2max, wsbio2scale,    &
205      &                   niter1max, niter2max, wfep, ldocp, ldocz, lthet
206#else
207      NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2, wsbio2max, wsbio2scale, niter1max, niter2max
208#endif
209      NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp
210      NAMELIST/nampismass/ ln_check_mass
211      INTEGER :: ios                 ! Local integer output status for namelist read
212      !!----------------------------------------------------------------------
213
214      REWIND( numnatp_ref )              ! Namelist nampisbio in reference namelist : Pisces variables
215      READ  ( numnatp_ref, nampisbio, IOSTAT = ios, ERR = 901)
216901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisbio in reference namelist', lwp )
217
218      REWIND( numnatp_cfg )              ! Namelist nampisbio in configuration namelist : Pisces variables
219      READ  ( numnatp_cfg, nampisbio, IOSTAT = ios, ERR = 902 )
220902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisbio in configuration namelist', lwp )
221      IF(lwm) WRITE ( numonp, nampisbio )
222
223      IF(lwp) THEN                         ! control print
224         WRITE(numout,*) ' Namelist : nampisbio'
225         WRITE(numout,*) '    frequence pour la biologie                nrdttrc   =', nrdttrc
226         WRITE(numout,*) '    POC sinking speed                         wsbio     =', wsbio
227         WRITE(numout,*) '    half saturation constant for mortality    xkmort    =', xkmort
228         WRITE(numout,*) '    Fe/C in zooplankton                       ferat3    =', ferat3
229         WRITE(numout,*) '    Big particles sinking speed               wsbio2    =', wsbio2
230         WRITE(numout,*) '    Big particles maximum sinking speed       wsbio2max =', wsbio2max
231         WRITE(numout,*) '    Big particles sinking speed length scale  wsbio2scale =', wsbio2scale
232         WRITE(numout,*) '    Maximum number of iterations for POC      niter1max =', niter1max
233         WRITE(numout,*) '    Maximum number of iterations for GOC      niter2max =', niter2max
234#if defined key_ligand
235         WRITE(numout,*) '    FeP sinking speed                             wfep  =', wfep
236         WRITE(numout,*) '    Phyto ligand production per unit doc          ldocp =', ldocp
237         WRITE(numout,*) '    Zoo ligand production per unit doc            ldocz =', ldocz
238         WRITE(numout,*) '    Proportional loss of ligands due to Fe uptake lthet =', lthet
239#endif
240      ENDIF
241
242      REWIND( numnatp_ref )              ! Namelist nampisdmp in reference namelist : Pisces damping
243      READ  ( numnatp_ref, nampisdmp, IOSTAT = ios, ERR = 905)
244905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisdmp in reference namelist', lwp )
245
246      REWIND( numnatp_cfg )              ! Namelist nampisdmp in configuration namelist : Pisces damping
247      READ  ( numnatp_cfg, nampisdmp, IOSTAT = ios, ERR = 906 )
248906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisdmp in configuration namelist', lwp )
249      IF(lwm) WRITE ( numonp, nampisdmp )
250
251      IF(lwp) THEN                         ! control print
252         WRITE(numout,*)
253         WRITE(numout,*) ' Namelist : nampisdmp'
254         WRITE(numout,*) '    Relaxation of tracer to glodap mean value             ln_pisdmp      =', ln_pisdmp
255         WRITE(numout,*) '    Frequency of Relaxation                               nn_pisdmp      =', nn_pisdmp
256         WRITE(numout,*) ' '
257      ENDIF
258
259      REWIND( numnatp_ref )              ! Namelist nampismass in reference namelist : Pisces mass conservation check
260      READ  ( numnatp_ref, nampismass, IOSTAT = ios, ERR = 907)
261907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismass in reference namelist', lwp )
262
263      REWIND( numnatp_cfg )              ! Namelist nampismass in configuration namelist : Pisces mass conservation check
264      READ  ( numnatp_cfg, nampismass, IOSTAT = ios, ERR = 908 )
265908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismass in configuration namelist', lwp )
266      IF(lwm) WRITE ( numonp, nampismass )
267
268      IF(lwp) THEN                         ! control print
269         WRITE(numout,*) ' '
270         WRITE(numout,*) ' Namelist parameter for mass conservation checking'
271         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
272         WRITE(numout,*) '    Flag to check mass conservation of NO3/Si/TALK ln_check_mass = ', ln_check_mass
273      ENDIF
274
275   END SUBROUTINE p4z_sms_init
276
277   SUBROUTINE p4z_rst( kt, cdrw )
278      !!---------------------------------------------------------------------
279      !!                   ***  ROUTINE p4z_rst  ***
280      !!
281      !!  ** Purpose : Read or write variables in restart file:
282      !!
283      !!  WRITE(READ) mode:
284      !!       kt        : number of time step since the begining of the experiment at the
285      !!                   end of the current(previous) run
286      !!---------------------------------------------------------------------
287      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
288      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
289      !!---------------------------------------------------------------------
290
291      IF( TRIM(cdrw) == 'READ' ) THEN
292         !
293         IF(lwp) WRITE(numout,*)
294         IF(lwp) WRITE(numout,*) ' p4z_rst : Read specific variables from pisces model '
295         IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
296         !
297         IF( iom_varid( numrtr, 'PH', ldstop = .FALSE. ) > 0 ) THEN
298            CALL iom_get( numrtr, jpdom_autoglo, 'PH' , hi(:,:,:)  )
299         ELSE
300            CALL ahini_for_at(hi)
301         ENDIF
302         CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:) )
303         IF( iom_varid( numrtr, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN
304            CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax' , xksimax(:,:)  )
305         ELSE
306            xksimax(:,:) = xksi(:,:)
307         ENDIF
308         !
309         IF( iom_varid( numrtr, 'tcflxcum', ldstop = .FALSE. ) > 0 ) THEN  ! cumulative total flux of carbon
310            CALL iom_get( numrtr, 'tcflxcum' , t_oce_co2_flx_cum  )
311         ELSE
312            t_oce_co2_flx_cum = 0._wp
313         ENDIF
314         !
315      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
316         IF( kt == nitrst ) THEN
317            IF(lwp) WRITE(numout,*)
318            IF(lwp) WRITE(numout,*) 'p4z_rst : write pisces restart file  kt =', kt
319            IF(lwp) WRITE(numout,*) '~~~~~~~'
320         ENDIF
321         CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:) )
322         CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) )
323         CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) )
324         CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum )
325      ENDIF
326      !
327   END SUBROUTINE p4z_rst
328
329   SUBROUTINE p4z_dmp( kt )
330      !!----------------------------------------------------------------------
331      !!                    ***  p4z_dmp  ***
332      !!
333      !! ** purpose  : Relaxation of some tracers
334      !!----------------------------------------------------------------------
335      !
336      INTEGER, INTENT( in )  ::     kt ! time step
337      !
338      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
339      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
340      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
341      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
342      !
343      REAL(wp) :: zarea, zalksumn, zpo4sumn, zno3sumn, zsilsumn
344      REAL(wp) :: zalksumb, zpo4sumb, zno3sumb, zsilsumb
345      !!---------------------------------------------------------------------
346
347
348      IF(lwp)  WRITE(numout,*)
349      IF(lwp)  WRITE(numout,*) ' p4z_dmp : Restoring of nutrients at time-step kt = ', kt
350      IF(lwp)  WRITE(numout,*)
351
352      IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA configuration (not 1D) !
353         !                                                    ! --------------------------- !
354         ! set total alkalinity, phosphate, nitrate & silicate
355         zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6             
356
357         zalksumn = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
358         zpo4sumn = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r
359         zno3sumn = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3
360         zsilsumn = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
361 
362         IF(lwp) WRITE(numout,*) '       TALKN mean : ', zalksumn
363         trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksumn
364
365         IF(lwp) WRITE(numout,*) '       PO4N  mean : ', zpo4sumn
366         trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sumn
367
368         IF(lwp) WRITE(numout,*) '       NO3N  mean : ', zno3sumn
369         trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sumn
370
371         IF(lwp) WRITE(numout,*) '       SiO3N mean : ', zsilsumn
372         trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsumn )
373         !
374         !
375         IF( .NOT. ln_top_euler ) THEN
376            zalksumb = glob_sum( trb(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
377            zpo4sumb = glob_sum( trb(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r
378            zno3sumb = glob_sum( trb(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3
379            zsilsumb = glob_sum( trb(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
380 
381            IF(lwp) WRITE(numout,*) ' '
382            IF(lwp) WRITE(numout,*) '       TALKB mean : ', zalksumb
383            trb(:,:,:,jptal) = trb(:,:,:,jptal) * alkmean / zalksumb
384
385            IF(lwp) WRITE(numout,*) '       PO4B  mean : ', zpo4sumb
386            trb(:,:,:,jppo4) = trb(:,:,:,jppo4) * po4mean / zpo4sumb
387
388            IF(lwp) WRITE(numout,*) '       NO3B  mean : ', zno3sumb
389            trb(:,:,:,jpno3) = trb(:,:,:,jpno3) * no3mean / zno3sumb
390
391            IF(lwp) WRITE(numout,*) '       SiO3B mean : ', zsilsumb
392            trb(:,:,:,jpsil) = MIN( 400.e-6,trb(:,:,:,jpsil) * silmean / zsilsumb )
393        ENDIF
394        !
395      ENDIF
396        !
397   END SUBROUTINE p4z_dmp
398
399
400   SUBROUTINE p4z_chk_mass( kt )
401      !!----------------------------------------------------------------------
402      !!                  ***  ROUTINE p4z_chk_mass  ***
403      !!
404      !! ** Purpose :  Mass conservation check
405      !!
406      !!---------------------------------------------------------------------
407      !
408      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
409      REAL(wp)             ::  zrdenittot, zsdenittot, znitrpottot
410      CHARACTER(LEN=100)   ::   cltxt
411      INTEGER :: jk
412      !!----------------------------------------------------------------------
413
414      !
415      !!---------------------------------------------------------------------
416
417      IF( kt == nittrc000 ) THEN
418         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si, Fer
419            CALL ctl_opn( numco2, 'carbon.budget'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
420            CALL ctl_opn( numnut, 'nutrient.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
421            CALL ctl_opn( numnit, 'nitrogen.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
422            xfact1 = rfact2r * 12. / 1.e15 * ryyss    ! conversion molC/kt --> PgC/yr
423            xfact2 = 1.e+3 * rno3 * 14. / 1.e12 * ryyss   ! conversion molC/l/s ----> TgN/m3/yr
424            xfact3 = 1.e+3 * rfact2r * rno3   ! conversion molC/l/kt ----> molN/m3/s
425            cltxt='time-step   Alkalinity        Nitrate        Phosphorus         Silicate           Iron'
426            IF( lwp ) WRITE(numnut,*)  TRIM(cltxt)
427            IF( lwp ) WRITE(numnut,*) 
428         ENDIF
429      ENDIF
430
431      !
432      IF( iom_use( "pno3tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
433         !   Compute the budget of NO3, ALK, Si, Fer
434         no3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  &
435            &                    + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
436            &                    + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
437            &                    + trn(:,:,:,jppoc)                     &
438            &                    + trn(:,:,:,jpgoc)                     &
439            &                    + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )
440         !
441         no3budget = no3budget / areatot
442         CALL iom_put( "pno3tot", no3budget )
443      ENDIF
444      !
445      IF( iom_use( "ppo4tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
446         po4budget = glob_sum( (   trn(:,:,:,jppo4)                     &
447            &                    + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
448            &                    + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
449            &                    + trn(:,:,:,jppoc)                     &
450            &                    + trn(:,:,:,jpgoc)                     &
451            &                    + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )
452         po4budget = po4budget / areatot
453         CALL iom_put( "ppo4tot", po4budget )
454      ENDIF
455      !
456      IF( iom_use( "psiltot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
457         silbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  &
458            &                    + trn(:,:,:,jpdsi)                     ) * cvol(:,:,:)  )
459         !
460         silbudget = silbudget / areatot
461         CALL iom_put( "psiltot", silbudget )
462      ENDIF
463      !
464      IF( iom_use( "palktot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
465         alkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              &
466            &                    + trn(:,:,:,jptal)                     &
467            &                    + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  )
468         !
469         alkbudget = alkbudget / areatot
470         CALL iom_put( "palktot", alkbudget )
471      ENDIF
472      !
473      IF( iom_use( "pfertot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
474         ferbudget = glob_sum( (   trn(:,:,:,jpfer) + trn(:,:,:,jpnfe)  &
475            &                    + trn(:,:,:,jpdfe)                     &
476            &                    + trn(:,:,:,jpbfe)                     &
477#if defined key_ligand
478            &                    + trn(:,:,:,jpfep)                     &
479#endif
480            &                    + trn(:,:,:,jpsfe)                     &
481            &                    + trn(:,:,:,jpzoo) * ferat3            &
482            &                    + trn(:,:,:,jpmes) * ferat3            ) * cvol(:,:,:)  )
483         !
484         ferbudget = ferbudget / areatot
485         CALL iom_put( "pfertot", ferbudget )
486      ENDIF
487      !
488
489      ! Global budget of N SMS : denitrification in the water column and in the sediment
490      !                          nitrogen fixation by the diazotrophs
491      ! --------------------------------------------------------------------------------
492      IF( iom_use( "tnfix" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
493         znitrpottot  = glob_sum ( nitrpot(:,:,:) * nitrfix * cvol(:,:,:) )
494         CALL iom_put( "tnfix"  , znitrpottot * 1.e+3 * rno3 )  ! Global  nitrogen fixation molC/l  to molN/m3
495      ENDIF
496      !
497      IF( iom_use( "tdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
498         zrdenittot   = glob_sum ( denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) )
499         CALL iom_put( "tdenit"  , zrdenittot * 1.e+3 * rno3 )  ! Total denitrification molC/l to molN/m3
500      ENDIF
501      !
502      IF( iom_use( "Sdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
503         zsdenittot   = glob_sum ( sdenit(:,:) * e1e2t(:,:) )
504         CALL iom_put( "Sdenit", sdenit(:,:) * xfact3 * tmask(:,:,1) )  ! Nitrate reduction in the sediments
505      ENDIF
506
507      IF( ln_check_mass .AND. kt == nitend ) THEN   ! Compute the budget of NO3, ALK, Si, Fer
508         t_atm_co2_flx  = t_atm_co2_flx / glob_sum( e1e2t(:,:) )
509         t_oce_co2_flx  = t_oce_co2_flx         * xfact1 * (-1 )
510         tpp            = tpp           * 1000. * xfact1
511         t_oce_co2_exp  = t_oce_co2_exp * 1000. * xfact1
512         IF( lwp ) WRITE(numco2,9000) ndastp, t_atm_co2_flx, t_oce_co2_flx, tpp, t_oce_co2_exp
513         IF( lwp ) WRITE(numnut,9100) ndastp, alkbudget        * 1.e+06, &
514             &                                no3budget * rno3 * 1.e+06, &
515             &                                po4budget * po4r * 1.e+06, &
516             &                                silbudget        * 1.e+06, &
517             &                                ferbudget        * 1.e+09
518         !
519         IF( lwp ) WRITE(numnit,9200) ndastp, znitrpottot * xfact2  , &
520         &                             zrdenittot  * xfact2  , &
521         &                             zsdenittot  * xfact2
522
523      ENDIF
524      !
525 9000  FORMAT(i8,f10.5,e18.10,f10.5,f10.5)
526 9100  FORMAT(i8,5e18.10)
527 9200  FORMAT(i8,3f10.5)
528
529       !
530   END SUBROUTINE p4z_chk_mass
531
532#else
533   !!======================================================================
534   !!  Dummy module :                                   No PISCES bio-model
535   !!======================================================================
536CONTAINS
537   SUBROUTINE p4z_sms( kt )                   ! Empty routine
538      INTEGER, INTENT( in ) ::   kt
539      WRITE(*,*) 'p4z_sms: You should not have seen this print! error?', kt
540   END SUBROUTINE p4z_sms
541#endif 
542
543   !!======================================================================
544END MODULE p4zsms 
Note: See TracBrowser for help on using the repository browser.