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

source: branches/2015/nemo_v3_6_STABLE/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90 @ 8532

Last change on this file since 8532 was 8532, checked in by cetlod, 7 years ago

v3.6 stable: bugfixes to solve problem particle in PISCES, see ticket #1940

File size: 26.2 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#if defined key_kriest
74      REAL(wp) ::  zcoef1, zcoef2
75#endif
76      CHARACTER (len=25) :: charout
77      !!---------------------------------------------------------------------
78      !
79      IF( nn_timing == 1 )  CALL timing_start('p4z_sms')
80      !
81      IF( kt == nittrc000 ) THEN
82        !
83        ALLOCATE( xnegtr(jpi,jpj,jpk) )
84        !
85        CALL p4z_che                              ! initialize the chemical constants
86        !
87        IF( .NOT. ln_rsttr ) THEN  ;   CALL p4z_che_ahini( hi )   !  set PH at kt=nit000
88        ELSE                       ;   CALL p4z_rst( nittrc000, 'READ' )  !* read or initialize all required fields
89        ENDIF
90        !
91      ENDIF
92      !
93      IF( ln_pisdmp .AND. MOD( kt - nn_dttrc, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt )      ! Relaxation of some tracers
94      !
95      !                                                                    !   set time step size (Euler/Leapfrog)
96      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN   ;    rfact = rdttrc(1)     !  at nittrc000
97      ELSEIF( kt <= nittrc000 + nn_dttrc )                          THEN   ;    rfact = 2. * rdttrc(1)   ! at nittrc000 or nittrc000+nn_dttrc (Leapfrog)
98      ENDIF
99      !
100      IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + nn_dttrc ) ) THEN
101         rfactr  = 1. / rfact
102         rfact2  = rfact / FLOAT( nrdttrc )
103         rfact2r = 1. / rfact2
104         xstep = rfact2 / rday         ! Time step duration for biology
105         IF(lwp) WRITE(numout,*) 
106         IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdttra(1)
107         IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2
108         IF(lwp) WRITE(numout,*)
109      ENDIF
110
111      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN
112         DO jn = jp_pcs0, jp_pcs1              !   SMS on tracer without Asselin time-filter
113            trb(:,:,:,jn) = trn(:,:,:,jn)
114         END DO
115      ENDIF
116      !
117      IF( ndayflxtr /= nday_year ) THEN      ! New days
118         !
119         ndayflxtr = nday_year
120
121         IF(lwp) write(numout,*)
122         IF(lwp) write(numout,*) ' New chemical constants and various rates for biogeochemistry at new day : ', nday_year
123         IF(lwp) write(numout,*) '~~~~~~'
124
125         CALL p4z_che              ! computation of chemical constants
126         CALL p4z_int( kt )        ! computation of various rates for biogeochemistry
127         !
128      ENDIF
129
130      IF( ll_sbc ) CALL p4z_sbc( kt )   ! external sources of nutrients
131
132      DO jnt = 1, nrdttrc          ! Potential time splitting if requested
133         !
134         CALL p4z_bio( kt, jnt )   ! Biology
135         CALL p4z_lys( kt, jnt )   ! Compute CaCO3 saturation
136         CALL p4z_sed( kt, jnt )   ! Surface and Bottom boundary conditions
137         CALL p4z_flx( kt, jnt )   ! Compute surface fluxes
138         !
139         xnegtr(:,:,:) = 1.e0
140         DO jn = jp_pcs0, jp_pcs1
141            DO jk = 1, jpk
142               DO jj = 1, jpj
143                  DO ji = 1, jpi
144                     IF( ( trb(ji,jj,jk,jn) + tra(ji,jj,jk,jn) ) < 0.e0 ) THEN
145                        ztra             = ABS( trb(ji,jj,jk,jn) ) / ( ABS( tra(ji,jj,jk,jn) ) + rtrn )
146                        xnegtr(ji,jj,jk) = MIN( xnegtr(ji,jj,jk),  ztra )
147                     ENDIF
148                 END DO
149               END DO
150            END DO
151         END DO
152         !                                ! where at least 1 tracer concentration becomes negative
153         !                                !
154         DO jn = jp_pcs0, jp_pcs1
155           trb(:,:,:,jn) = trb(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn)
156         END DO
157        !
158         DO jn = jp_pcs0, jp_pcs1
159            tra(:,:,:,jn) = 0._wp
160         END DO
161         !
162         IF( ln_top_euler ) THEN
163            DO jn = jp_pcs0, jp_pcs1
164               trn(:,:,:,jn) = trb(:,:,:,jn)
165            END DO
166         ENDIF
167      END DO
168
169#if defined key_kriest
170      !
171      zcoef1 = 1.e0 / xkr_massp 
172      zcoef2 = 1.e0 / xkr_massp / 1.1
173      DO jk = 1,jpkm1
174         trb(:,:,jk,jpnum) = MAX(  trb(:,:,jk,jpnum), trb(:,:,jk,jppoc) * zcoef1 / xnumm(jk)  )
175         trb(:,:,jk,jpnum) = MIN(  trb(:,:,jk,jpnum), trb(:,:,jk,jppoc) * zcoef2              )
176      END DO
177      !
178#endif
179      !
180      !
181      IF( l_trdtrc ) THEN
182         DO jn = jp_pcs0, jp_pcs1
183           CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt )   ! save trends
184         END DO
185      END IF
186      !
187      IF( lk_sed ) THEN 
188         !
189         CALL sed_model( kt )     !  Main program of Sediment model
190         !
191         DO jn = jp_pcs0, jp_pcs1
192           CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. )
193         END DO
194         !
195      ENDIF
196      !
197      IF( lrst_trc )  CALL p4z_rst( kt, 'WRITE' )  !* Write PISCES informations in restart file
198      !
199
200      IF( lk_iomput .OR. ln_check_mass )  CALL p4z_chk_mass( kt ) ! Mass conservation checking
201
202      IF ( lwm .AND. kt == nittrc000 ) CALL FLUSH    ( numonp )     ! flush output namelist PISCES
203      IF( nn_timing == 1 )  CALL timing_stop('p4z_sms')
204      !
205      !
206   END SUBROUTINE p4z_sms
207
208   SUBROUTINE p4z_sms_init
209      !!----------------------------------------------------------------------
210      !!                     ***  p4z_sms_init  *** 
211      !!
212      !! ** Purpose :   read PISCES namelist
213      !!
214      !! ** input   :   file 'namelist.trc.s' containing the following
215      !!             namelist: natext, natbio, natsms
216      !!                       natkriest ("key_kriest")
217      !!----------------------------------------------------------------------
218      NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2, niter1max, niter2max
219#if defined key_kriest
220      NAMELIST/nampiskrp/ xkr_eta, xkr_zeta, xkr_ncontent, xkr_mass_min, xkr_mass_max
221#endif
222      NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp
223      NAMELIST/nampismass/ ln_check_mass
224      INTEGER :: ios                 ! Local integer output status for namelist read
225      !!----------------------------------------------------------------------
226
227      REWIND( numnatp_ref )              ! Namelist nampisbio in reference namelist : Pisces variables
228      READ  ( numnatp_ref, nampisbio, IOSTAT = ios, ERR = 901)
229901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisbio in reference namelist', lwp )
230
231      REWIND( numnatp_cfg )              ! Namelist nampisbio in configuration namelist : Pisces variables
232      READ  ( numnatp_cfg, nampisbio, IOSTAT = ios, ERR = 902 )
233902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisbio in configuration namelist', lwp )
234      IF(lwm) WRITE ( numonp, nampisbio )
235
236      IF(lwp) THEN                         ! control print
237         WRITE(numout,*) ' Namelist : nampisbio'
238         WRITE(numout,*) '    frequence pour la biologie                nrdttrc   =', nrdttrc
239         WRITE(numout,*) '    POC sinking speed                         wsbio     =', wsbio
240         WRITE(numout,*) '    half saturation constant for mortality    xkmort    =', xkmort
241         WRITE(numout,*) '    Fe/C in zooplankton                       ferat3    =', ferat3
242         WRITE(numout,*) '    Big particles sinking speed               wsbio2    =', wsbio2
243         WRITE(numout,*) '    Maximum number of iterations for POC      niter1max =', niter1max
244         WRITE(numout,*) '    Maximum number of iterations for GOC      niter2max =', niter2max
245      ENDIF
246
247#if defined key_kriest
248
249      !                               ! nampiskrp : kriest parameters
250      !                               ! -----------------------------
251      REWIND( numnatp_ref )              ! Namelist nampiskrp in reference namelist : Pisces Kriest
252      READ  ( numnatp_ref, nampiskrp, IOSTAT = ios, ERR = 903)
253903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampiskrp in reference namelist', lwp )
254
255      REWIND( numnatp_cfg )              ! Namelist nampiskrp in configuration namelist : Pisces Kriest
256      READ  ( numnatp_cfg, nampiskrp, IOSTAT = ios, ERR = 904 )
257904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampiskrp in configuration namelist', lwp )
258      IF(lwm) WRITE ( numonp, nampiskrp )
259
260      IF(lwp) THEN
261         WRITE(numout,*)
262         WRITE(numout,*) ' Namelist : nampiskrp'
263         WRITE(numout,*) '    Sinking  exponent                        xkr_eta      = ', xkr_eta
264         WRITE(numout,*) '    N content exponent                       xkr_zeta     = ', xkr_zeta
265         WRITE(numout,*) '    N content factor                         xkr_ncontent = ', xkr_ncontent
266         WRITE(numout,*) '    Minimum mass for Aggregates              xkr_mass_min = ', xkr_mass_min
267         WRITE(numout,*) '    Maximum mass for Aggregates              xkr_mass_max = ', xkr_mass_max
268         WRITE(numout,*)
269     ENDIF
270
271
272     ! Computation of some variables
273     xkr_massp = xkr_ncontent * 7.625 * xkr_mass_min**xkr_zeta
274
275#endif
276
277      REWIND( numnatp_ref )              ! Namelist nampisdmp in reference namelist : Pisces damping
278      READ  ( numnatp_ref, nampisdmp, IOSTAT = ios, ERR = 905)
279905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisdmp in reference namelist', lwp )
280
281      REWIND( numnatp_cfg )              ! Namelist nampisdmp in configuration namelist : Pisces damping
282      READ  ( numnatp_cfg, nampisdmp, IOSTAT = ios, ERR = 906 )
283906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisdmp in configuration namelist', lwp )
284      IF(lwm) WRITE ( numonp, nampisdmp )
285
286      IF(lwp) THEN                         ! control print
287         WRITE(numout,*)
288         WRITE(numout,*) ' Namelist : nampisdmp'
289         WRITE(numout,*) '    Relaxation of tracer to glodap mean value             ln_pisdmp      =', ln_pisdmp
290         WRITE(numout,*) '    Frequency of Relaxation                               nn_pisdmp      =', nn_pisdmp
291         WRITE(numout,*) ' '
292      ENDIF
293
294      REWIND( numnatp_ref )              ! Namelist nampismass in reference namelist : Pisces mass conservation check
295      READ  ( numnatp_ref, nampismass, IOSTAT = ios, ERR = 907)
296907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismass in reference namelist', lwp )
297
298      REWIND( numnatp_cfg )              ! Namelist nampismass in configuration namelist : Pisces mass conservation check
299      READ  ( numnatp_cfg, nampismass, IOSTAT = ios, ERR = 908 )
300908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismass in configuration namelist', lwp )
301      IF(lwm) WRITE ( numonp, nampismass )
302
303      IF(lwp) THEN                         ! control print
304         WRITE(numout,*) ' '
305         WRITE(numout,*) ' Namelist parameter for mass conservation checking'
306         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
307         WRITE(numout,*) '    Flag to check mass conservation of NO3/Si/TALK ln_check_mass = ', ln_check_mass
308      ENDIF
309
310   END SUBROUTINE p4z_sms_init
311
312   SUBROUTINE p4z_rst( kt, cdrw )
313      !!---------------------------------------------------------------------
314      !!                   ***  ROUTINE p4z_rst  ***
315      !!
316      !!  ** Purpose : Read or write variables in restart file:
317      !!
318      !!  WRITE(READ) mode:
319      !!       kt        : number of time step since the begining of the experiment at the
320      !!                   end of the current(previous) run
321      !!---------------------------------------------------------------------
322      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
323      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
324      !!---------------------------------------------------------------------
325
326      IF( TRIM(cdrw) == 'READ' ) THEN
327         !
328         IF(lwp) WRITE(numout,*)
329         IF(lwp) WRITE(numout,*) ' p4z_rst : Read specific variables from pisces model '
330         IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
331         !
332         IF( iom_varid( numrtr, 'PH', ldstop = .FALSE. ) > 0 ) THEN
333            CALL iom_get( numrtr, jpdom_autoglo, 'PH' , hi(:,:,:)  )
334         ELSE
335            CALL p4z_che_ahini( hi )
336         ENDIF
337         CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:) )
338         IF( iom_varid( numrtr, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN
339            CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax' , xksimax(:,:)  )
340         ELSE
341            xksimax(:,:) = xksi(:,:)
342         ENDIF
343         !
344         IF( iom_varid( numrtr, 'tcflxcum', ldstop = .FALSE. ) > 0 ) THEN  ! cumulative total flux of carbon
345            CALL iom_get( numrtr, 'tcflxcum' , t_oce_co2_flx_cum  )
346         ELSE
347            t_oce_co2_flx_cum = 0._wp
348         ENDIF
349         !
350      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
351         IF( kt == nitrst ) THEN
352            IF(lwp) WRITE(numout,*)
353            IF(lwp) WRITE(numout,*) 'p4z_rst : write pisces restart file  kt =', kt
354            IF(lwp) WRITE(numout,*) '~~~~~~~'
355         ENDIF
356         CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:) )
357         CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) )
358         CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) )
359         CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum )
360      ENDIF
361      !
362   END SUBROUTINE p4z_rst
363
364   SUBROUTINE p4z_dmp( kt )
365      !!----------------------------------------------------------------------
366      !!                    ***  p4z_dmp  ***
367      !!
368      !! ** purpose  : Relaxation of some tracers
369      !!----------------------------------------------------------------------
370      !
371      INTEGER, INTENT( in )  ::     kt ! time step
372      !
373      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
374      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
375      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
376      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
377      !
378      REAL(wp) :: zarea, zalksumn, zpo4sumn, zno3sumn, zsilsumn
379      REAL(wp) :: zalksumb, zpo4sumb, zno3sumb, zsilsumb
380      !!---------------------------------------------------------------------
381
382
383      IF(lwp)  WRITE(numout,*)
384      IF(lwp)  WRITE(numout,*) ' p4z_dmp : Restoring of nutrients at time-step kt = ', kt
385      IF(lwp)  WRITE(numout,*)
386
387      IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA configuration (not 1D) !
388         !                                                    ! --------------------------- !
389         ! set total alkalinity, phosphate, nitrate & silicate
390         zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6             
391
392         zalksumn = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
393         zpo4sumn = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r
394         zno3sumn = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3
395         zsilsumn = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
396 
397         IF(lwp) WRITE(numout,*) '       TALKN mean : ', zalksumn
398         trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksumn
399
400         IF(lwp) WRITE(numout,*) '       PO4N  mean : ', zpo4sumn
401         trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sumn
402
403         IF(lwp) WRITE(numout,*) '       NO3N  mean : ', zno3sumn
404         trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sumn
405
406         IF(lwp) WRITE(numout,*) '       SiO3N mean : ', zsilsumn
407         trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsumn )
408         !
409         !
410         IF( .NOT. ln_top_euler ) THEN
411            zalksumb = glob_sum( trb(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
412            zpo4sumb = glob_sum( trb(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r
413            zno3sumb = glob_sum( trb(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3
414            zsilsumb = glob_sum( trb(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
415 
416            IF(lwp) WRITE(numout,*) ' '
417            IF(lwp) WRITE(numout,*) '       TALKB mean : ', zalksumb
418            trb(:,:,:,jptal) = trb(:,:,:,jptal) * alkmean / zalksumb
419
420            IF(lwp) WRITE(numout,*) '       PO4B  mean : ', zpo4sumb
421            trb(:,:,:,jppo4) = trb(:,:,:,jppo4) * po4mean / zpo4sumb
422
423            IF(lwp) WRITE(numout,*) '       NO3B  mean : ', zno3sumb
424            trb(:,:,:,jpno3) = trb(:,:,:,jpno3) * no3mean / zno3sumb
425
426            IF(lwp) WRITE(numout,*) '       SiO3B mean : ', zsilsumb
427            trb(:,:,:,jpsil) = MIN( 400.e-6,trb(:,:,:,jpsil) * silmean / zsilsumb )
428        ENDIF
429        !
430      ENDIF
431        !
432   END SUBROUTINE p4z_dmp
433
434
435   SUBROUTINE p4z_chk_mass( kt )
436      !!----------------------------------------------------------------------
437      !!                  ***  ROUTINE p4z_chk_mass  ***
438      !!
439      !! ** Purpose :  Mass conservation check
440      !!
441      !!---------------------------------------------------------------------
442      !
443      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
444      REAL(wp)             ::  zrdenittot, zsdenittot, znitrpottot
445      CHARACTER(LEN=100)   ::   cltxt
446      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
447      INTEGER :: jk
448      !!----------------------------------------------------------------------
449
450      !
451      !!---------------------------------------------------------------------
452
453      IF( kt == nittrc000 ) THEN
454         xfact1 = rfact2r * 12. / 1.e15 * ryyss    ! conversion molC/kt --> PgC/yr
455         xfact2 = 1.e+3 * rno3 * 14. / 1.e12 * ryyss   ! conversion molC/l/s ----> TgN/m3/yr
456         xfact3 = 1.e+3 * rfact2r * rno3   ! conversion molC/l/kt ----> molN/m3/s
457         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si, Fer
458            CALL ctl_opn( numco2, 'carbon.budget'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
459            CALL ctl_opn( numnut, 'nutrient.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
460            CALL ctl_opn( numnit, 'nitrogen.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
461            cltxt='time-step   Alkalinity        Nitrate        Phosphorus         Silicate           Iron'
462            IF( lwp ) WRITE(numnut,*)  TRIM(cltxt)
463            IF( lwp ) WRITE(numnut,*) 
464         ENDIF
465      ENDIF
466
467      !
468      IF( iom_use( "pno3tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
469         !   Compute the budget of NO3, ALK, Si, Fer
470         no3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  &
471            &                    + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
472            &                    + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
473            &                    + trn(:,:,:,jppoc)                     &
474#if ! defined key_kriest
475            &                    + trn(:,:,:,jpgoc)                     &
476#endif
477            &                    + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )
478         !
479         no3budget = no3budget / areatot
480         CALL iom_put( "pno3tot", no3budget )
481      ENDIF
482      !
483      IF( iom_use( "ppo4tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
484         po4budget = glob_sum( (   trn(:,:,:,jppo4)                     &
485            &                    + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
486            &                    + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
487            &                    + trn(:,:,:,jppoc)                     &
488#if ! defined key_kriest
489            &                    + trn(:,:,:,jpgoc)                     &
490#endif
491            &                    + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )
492         po4budget = po4budget / areatot
493         CALL iom_put( "ppo4tot", po4budget )
494      ENDIF
495      !
496      IF( iom_use( "psiltot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
497         silbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  &
498            &                    + trn(:,:,:,jpdsi)                     ) * cvol(:,:,:)  )
499         !
500         silbudget = silbudget / areatot
501         CALL iom_put( "psiltot", silbudget )
502      ENDIF
503      !
504      IF( iom_use( "palktot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
505         alkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              &
506            &                    + trn(:,:,:,jptal)                     &
507            &                    + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  )
508         !
509         alkbudget = alkbudget / areatot
510         CALL iom_put( "palktot", alkbudget )
511      ENDIF
512      !
513      IF( iom_use( "pfertot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
514         ferbudget = glob_sum( (   trn(:,:,:,jpfer) + trn(:,:,:,jpnfe)  &
515            &                    + trn(:,:,:,jpdfe)                     &
516#if ! defined key_kriest
517            &                    + trn(:,:,:,jpbfe)                     &
518#endif
519            &                    + trn(:,:,:,jpsfe)                     &
520            &                    + trn(:,:,:,jpzoo) * ferat3            &
521            &                    + trn(:,:,:,jpmes) * ferat3            ) * cvol(:,:,:)  )
522         !
523         ferbudget = ferbudget / areatot
524         CALL iom_put( "pfertot", ferbudget )
525      ENDIF
526      !
527
528      ! Global budget of N SMS : denitrification in the water column and in the sediment
529      !                          nitrogen fixation by the diazotrophs
530      ! --------------------------------------------------------------------------------
531      IF( iom_use( "tnfix" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
532         znitrpottot  = glob_sum ( nitrpot(:,:,:) * nitrfix * cvol(:,:,:) )
533         CALL iom_put( "tnfix"  , znitrpottot * xfact3 )  ! Global  nitrogen fixation molC/l  to molN/m3
534      ENDIF
535      !
536      IF( iom_use( "tdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
537         zrdenittot = glob_sum ( denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) ) ! denitrification in the water column
538         zsdenittot = glob_sum ( sdenit(:,:) * e1e2t(:,:) * tmask(:,:,1) )              ! denitrification in the sediments
539         CALL iom_put( "tdenit"  , ( zrdenittot + zsdenittot ) * xfact3 )               ! Total denitrification in molN/m3
540      ENDIF
541
542      IF( ln_check_mass .AND. kt == nitend ) THEN   ! Compute the budget of NO3, ALK, Si, Fer
543         t_atm_co2_flx  = t_atm_co2_flx / glob_sum( e1e2t(:,:) )
544         t_oce_co2_flx  = t_oce_co2_flx         * xfact1 * (-1 )
545         tpp            = tpp           * 1000. * xfact1
546         t_oce_co2_exp  = t_oce_co2_exp * 1000. * xfact1
547         IF( lwp ) WRITE(numco2,9000) ndastp, t_atm_co2_flx, t_oce_co2_flx, tpp, t_oce_co2_exp
548         IF( lwp ) WRITE(numnut,9100) ndastp, alkbudget        * 1.e+06, &
549             &                                no3budget * rno3 * 1.e+06, &
550             &                                po4budget * po4r * 1.e+06, &
551             &                                silbudget        * 1.e+06, &
552             &                                ferbudget        * 1.e+09
553         !
554         IF( lwp ) WRITE(numnit,9200) ndastp, znitrpottot * xfact2  , &
555         &                             zrdenittot  * xfact2  , &
556         &                             zsdenittot  * xfact2
557
558      ENDIF
559      !
560 9000  FORMAT(i8,f10.5,e18.10,f10.5,f10.5)
561 9100  FORMAT(i8,5e18.10)
562 9200  FORMAT(i8,3f10.5)
563
564       !
565   END SUBROUTINE p4z_chk_mass
566
567#else
568   !!======================================================================
569   !!  Dummy module :                                   No PISCES bio-model
570   !!======================================================================
571CONTAINS
572   SUBROUTINE p4z_sms( kt )                   ! Empty routine
573      INTEGER, INTENT( in ) ::   kt
574      WRITE(*,*) 'p4z_sms: You should not have seen this print! error?', kt
575   END SUBROUTINE p4z_sms
576#endif 
577
578   !!======================================================================
579END MODULE p4zsms 
Note: See TracBrowser for help on using the repository browser.