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

source: branches/UKMO/dev_r8183_ICEMODEL_svn_removed/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90 @ 8733

Last change on this file since 8733 was 8733, checked in by dancopsey, 6 years ago

Remove svn keywords.

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