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/UKMO/r6232_obs_oper_update/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

source: branches/UKMO/r6232_obs_oper_update/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90 @ 11203

Last change on this file since 11203 was 11203, checked in by jcastill, 5 years ago

Remove the svn keywords that were introduced in the last modification

File size: 27.6 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$
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_ph_ini   !  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_sed( kt, jnt )   ! Sedimentation
136         CALL p4z_lys( kt, jnt )   ! Compute CaCO3 saturation
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_ph_ini
313      !!---------------------------------------------------------------------
314      !!                   ***  ROUTINE p4z_ini_ph  ***
315      !!
316      !!  ** Purpose : Initialization of chemical variables of the carbon cycle
317      !!---------------------------------------------------------------------
318      INTEGER  ::  ji, jj, jk
319      REAL(wp) ::  zcaralk, zbicarb, zco3
320      REAL(wp) ::  ztmas, ztmas1
321      !!---------------------------------------------------------------------
322
323      ! Set PH from  total alkalinity, borat (???), akb3 (???) and ak23 (???)
324      ! --------------------------------------------------------
325      DO jk = 1, jpk
326         DO jj = 1, jpj
327            DO ji = 1, jpi
328               ztmas   = tmask(ji,jj,jk)
329               ztmas1  = 1. - tmask(ji,jj,jk)
330               zcaralk = trb(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  )
331               zco3    = ( zcaralk - trb(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1
332               zbicarb = ( 2. * trb(ji,jj,jk,jpdic) - zcaralk )
333               hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1
334            END DO
335         END DO
336     END DO
337     !
338   END SUBROUTINE p4z_ph_ini
339
340   SUBROUTINE p4z_rst( kt, cdrw )
341      !!---------------------------------------------------------------------
342      !!                   ***  ROUTINE p4z_rst  ***
343      !!
344      !!  ** Purpose : Read or write variables in restart file:
345      !!
346      !!  WRITE(READ) mode:
347      !!       kt        : number of time step since the begining of the experiment at the
348      !!                   end of the current(previous) run
349      !!---------------------------------------------------------------------
350      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
351      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
352      !
353      INTEGER  ::  ji, jj, jk
354      REAL(wp) ::  zcaralk, zbicarb, zco3
355      REAL(wp) ::  ztmas, ztmas1
356      !!---------------------------------------------------------------------
357
358      IF( TRIM(cdrw) == 'READ' ) THEN
359         !
360         IF(lwp) WRITE(numout,*)
361         IF(lwp) WRITE(numout,*) ' p4z_rst : Read specific variables from pisces model '
362         IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
363         !
364         IF( iom_varid( numrtr, 'PH', ldstop = .FALSE. ) > 0 ) THEN
365            CALL iom_get( numrtr, jpdom_autoglo, 'PH' , hi(:,:,:)  )
366         ELSE
367!            hi(:,:,:) = 1.e-9
368            CALL p4z_ph_ini
369         ENDIF
370         CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:) )
371         IF( iom_varid( numrtr, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN
372            CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax' , xksimax(:,:)  )
373         ELSE
374            xksimax(:,:) = xksi(:,:)
375         ENDIF
376         !
377         IF( iom_varid( numrtr, 'tcflxcum', ldstop = .FALSE. ) > 0 ) THEN  ! cumulative total flux of carbon
378            CALL iom_get( numrtr, 'tcflxcum' , t_oce_co2_flx_cum  )
379         ELSE
380            t_oce_co2_flx_cum = 0._wp
381         ENDIF
382         !
383      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
384         IF( kt == nitrst ) THEN
385            IF(lwp) WRITE(numout,*)
386            IF(lwp) WRITE(numout,*) 'p4z_rst : write pisces restart file  kt =', kt
387            IF(lwp) WRITE(numout,*) '~~~~~~~'
388         ENDIF
389         CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:) )
390         CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) )
391         CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) )
392         CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum )
393      ENDIF
394      !
395   END SUBROUTINE p4z_rst
396
397   SUBROUTINE p4z_dmp( kt )
398      !!----------------------------------------------------------------------
399      !!                    ***  p4z_dmp  ***
400      !!
401      !! ** purpose  : Relaxation of some tracers
402      !!----------------------------------------------------------------------
403      !
404      INTEGER, INTENT( in )  ::     kt ! time step
405      !
406      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
407      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
408      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
409      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
410      !
411      REAL(wp) :: zarea, zalksumn, zpo4sumn, zno3sumn, zsilsumn
412      REAL(wp) :: zalksumb, zpo4sumb, zno3sumb, zsilsumb
413      !!---------------------------------------------------------------------
414
415
416      IF(lwp)  WRITE(numout,*)
417      IF(lwp)  WRITE(numout,*) ' p4z_dmp : Restoring of nutrients at time-step kt = ', kt
418      IF(lwp)  WRITE(numout,*)
419
420      IF( cp_cfg == "orca" .AND. .NOT. lk_c1d ) THEN      ! ORCA configuration (not 1D) !
421         !                                                    ! --------------------------- !
422         ! set total alkalinity, phosphate, nitrate & silicate
423         zarea          = 1._wp / glob_sum( cvol(:,:,:) ) * 1e6             
424
425         zalksumn = glob_sum( trn(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
426         zpo4sumn = glob_sum( trn(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r
427         zno3sumn = glob_sum( trn(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3
428         zsilsumn = glob_sum( trn(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
429 
430         IF(lwp) WRITE(numout,*) '       TALKN mean : ', zalksumn
431         trn(:,:,:,jptal) = trn(:,:,:,jptal) * alkmean / zalksumn
432
433         IF(lwp) WRITE(numout,*) '       PO4N  mean : ', zpo4sumn
434         trn(:,:,:,jppo4) = trn(:,:,:,jppo4) * po4mean / zpo4sumn
435
436         IF(lwp) WRITE(numout,*) '       NO3N  mean : ', zno3sumn
437         trn(:,:,:,jpno3) = trn(:,:,:,jpno3) * no3mean / zno3sumn
438
439         IF(lwp) WRITE(numout,*) '       SiO3N mean : ', zsilsumn
440         trn(:,:,:,jpsil) = MIN( 400.e-6,trn(:,:,:,jpsil) * silmean / zsilsumn )
441         !
442         !
443         IF( .NOT. ln_top_euler ) THEN
444            zalksumb = glob_sum( trb(:,:,:,jptal) * cvol(:,:,:)  ) * zarea
445            zpo4sumb = glob_sum( trb(:,:,:,jppo4) * cvol(:,:,:)  ) * zarea * po4r
446            zno3sumb = glob_sum( trb(:,:,:,jpno3) * cvol(:,:,:)  ) * zarea * rno3
447            zsilsumb = glob_sum( trb(:,:,:,jpsil) * cvol(:,:,:)  ) * zarea
448 
449            IF(lwp) WRITE(numout,*) ' '
450            IF(lwp) WRITE(numout,*) '       TALKB mean : ', zalksumb
451            trb(:,:,:,jptal) = trb(:,:,:,jptal) * alkmean / zalksumb
452
453            IF(lwp) WRITE(numout,*) '       PO4B  mean : ', zpo4sumb
454            trb(:,:,:,jppo4) = trb(:,:,:,jppo4) * po4mean / zpo4sumb
455
456            IF(lwp) WRITE(numout,*) '       NO3B  mean : ', zno3sumb
457            trb(:,:,:,jpno3) = trb(:,:,:,jpno3) * no3mean / zno3sumb
458
459            IF(lwp) WRITE(numout,*) '       SiO3B mean : ', zsilsumb
460            trb(:,:,:,jpsil) = MIN( 400.e-6,trb(:,:,:,jpsil) * silmean / zsilsumb )
461        ENDIF
462        !
463      ENDIF
464        !
465   END SUBROUTINE p4z_dmp
466
467
468   SUBROUTINE p4z_chk_mass( kt )
469      !!----------------------------------------------------------------------
470      !!                  ***  ROUTINE p4z_chk_mass  ***
471      !!
472      !! ** Purpose :  Mass conservation check
473      !!
474      !!---------------------------------------------------------------------
475      !
476      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
477      REAL(wp)             ::  zrdenittot, zsdenittot, znitrpottot
478      CHARACTER(LEN=100)   ::   cltxt
479      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvol
480      INTEGER :: jk
481      !!----------------------------------------------------------------------
482
483      !
484      !!---------------------------------------------------------------------
485
486      IF( kt == nittrc000 ) THEN
487         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si, Fer
488            CALL ctl_opn( numco2, 'carbon.budget'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
489            CALL ctl_opn( numnut, 'nutrient.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
490            CALL ctl_opn( numnit, 'nitrogen.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
491            xfact1 = rfact2r * 12. / 1.e15 * ryyss    ! conversion molC/kt --> PgC/yr
492            xfact2 = 1.e+3 * rno3 * 14. / 1.e12 * ryyss   ! conversion molC/l/s ----> TgN/m3/yr
493            xfact3 = 1.e+3 * rfact2r * rno3   ! conversion molC/l/kt ----> molN/m3/s
494            cltxt='time-step   Alkalinity        Nitrate        Phosphorus         Silicate           Iron'
495            IF( lwp ) WRITE(numnut,*)  TRIM(cltxt)
496            IF( lwp ) WRITE(numnut,*) 
497         ENDIF
498      ENDIF
499
500      !
501      IF( iom_use( "pno3tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
502         !   Compute the budget of NO3, ALK, Si, Fer
503         no3budget = glob_sum( (   trn(:,:,:,jpno3) + trn(:,:,:,jpnh4)  &
504            &                    + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
505            &                    + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
506            &                    + trn(:,:,:,jppoc)                     &
507#if ! defined key_kriest
508            &                    + trn(:,:,:,jpgoc)                     &
509#endif
510            &                    + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )
511         !
512         no3budget = no3budget / areatot
513         CALL iom_put( "pno3tot", no3budget )
514      ENDIF
515      !
516      IF( iom_use( "ppo4tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
517         po4budget = glob_sum( (   trn(:,:,:,jppo4)                     &
518            &                    + trn(:,:,:,jpphy) + trn(:,:,:,jpdia)  &
519            &                    + trn(:,:,:,jpzoo) + trn(:,:,:,jpmes)  &
520            &                    + trn(:,:,:,jppoc)                     &
521#if ! defined key_kriest
522            &                    + trn(:,:,:,jpgoc)                     &
523#endif
524            &                    + trn(:,:,:,jpdoc)                     ) * cvol(:,:,:)  )
525         po4budget = po4budget / areatot
526         CALL iom_put( "ppo4tot", po4budget )
527      ENDIF
528      !
529      IF( iom_use( "psiltot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
530         silbudget = glob_sum( (   trn(:,:,:,jpsil) + trn(:,:,:,jpgsi)  &
531            &                    + trn(:,:,:,jpdsi)                     ) * cvol(:,:,:)  )
532         !
533         silbudget = silbudget / areatot
534         CALL iom_put( "psiltot", silbudget )
535      ENDIF
536      !
537      IF( iom_use( "palktot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
538         alkbudget = glob_sum( (   trn(:,:,:,jpno3) * rno3              &
539            &                    + trn(:,:,:,jptal)                     &
540            &                    + trn(:,:,:,jpcal) * 2.                ) * cvol(:,:,:)  )
541         !
542         alkbudget = alkbudget / areatot
543         CALL iom_put( "palktot", alkbudget )
544      ENDIF
545      !
546      IF( iom_use( "pfertot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
547         ferbudget = glob_sum( (   trn(:,:,:,jpfer) + trn(:,:,:,jpnfe)  &
548            &                    + trn(:,:,:,jpdfe)                     &
549#if ! defined key_kriest
550            &                    + trn(:,:,:,jpbfe)                     &
551#endif
552            &                    + trn(:,:,:,jpsfe)                     &
553            &                    + trn(:,:,:,jpzoo) * ferat3            &
554            &                    + trn(:,:,:,jpmes) * ferat3            ) * cvol(:,:,:)  )
555         !
556         ferbudget = ferbudget / areatot
557         CALL iom_put( "pfertot", ferbudget )
558      ENDIF
559      !
560
561      ! Global budget of N SMS : denitrification in the water column and in the sediment
562      !                          nitrogen fixation by the diazotrophs
563      ! --------------------------------------------------------------------------------
564      IF( iom_use( "tnfix" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
565         znitrpottot  = glob_sum ( nitrpot(:,:,:) * nitrfix * cvol(:,:,:) )
566         CALL iom_put( "tnfix"  , znitrpottot * 1.e+3 * rno3 )  ! Global  nitrogen fixation molC/l  to molN/m3
567      ENDIF
568      !
569      IF( iom_use( "tdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
570         zrdenittot   = glob_sum ( denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) )
571         CALL iom_put( "tdenit"  , zrdenittot * 1.e+3 * rno3 )  ! Total denitrification molC/l to molN/m3
572      ENDIF
573      !
574      IF( iom_use( "Sdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
575         zsdenittot   = glob_sum ( sdenit(:,:) * e1e2t(:,:) )
576         CALL iom_put( "Sdenit", sdenit(:,:) * xfact3 * tmask(:,:,1) )  ! Nitrate reduction in the sediments
577      ENDIF
578
579      IF( ln_check_mass .AND. kt == nitend ) THEN   ! Compute the budget of NO3, ALK, Si, Fer
580         t_atm_co2_flx  = t_atm_co2_flx / glob_sum( e1e2t(:,:) )
581         t_oce_co2_flx  = t_oce_co2_flx         * xfact1 * (-1 )
582         tpp            = tpp           * 1000. * xfact1
583         t_oce_co2_exp  = t_oce_co2_exp * 1000. * xfact1
584         IF( lwp ) WRITE(numco2,9000) ndastp, t_atm_co2_flx, t_oce_co2_flx, tpp, t_oce_co2_exp
585         IF( lwp ) WRITE(numnut,9100) ndastp, alkbudget        * 1.e+06, &
586             &                                no3budget * rno3 * 1.e+06, &
587             &                                po4budget * po4r * 1.e+06, &
588             &                                silbudget        * 1.e+06, &
589             &                                ferbudget        * 1.e+09
590         !
591         IF( lwp ) WRITE(numnit,9200) ndastp, znitrpottot * xfact2  , &
592         &                             zrdenittot  * xfact2  , &
593         &                             zsdenittot  * xfact2
594
595      ENDIF
596      !
597 9000  FORMAT(i8,f10.5,e18.10,f10.5,f10.5)
598 9100  FORMAT(i8,5e18.10)
599 9200  FORMAT(i8,3f10.5)
600
601       !
602   END SUBROUTINE p4z_chk_mass
603
604#else
605   !!======================================================================
606   !!  Dummy module :                                   No PISCES bio-model
607   !!======================================================================
608CONTAINS
609   SUBROUTINE p4z_sms( kt )                   ! Empty routine
610      INTEGER, INTENT( in ) ::   kt
611      WRITE(*,*) 'p4z_sms: You should not have seen this print! error?', kt
612   END SUBROUTINE p4z_sms
613#endif 
614
615   !!======================================================================
616END MODULE p4zsms 
Note: See TracBrowser for help on using the repository browser.