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 NEMO/trunk/src/TOP/PISCES/P4Z – NEMO

source: NEMO/trunk/src/TOP/PISCES/P4Z/p4zsms.F90 @ 13295

Last change on this file since 13295 was 13295, checked in by acc, 4 years ago

Replace do-loop macros in the trunk with alternative forms with greater flexibility for extra halo applications. This alters a lot of routines but does not change any behaviour or results. do_loop_substitute.h90 is greatly simplified by this change. SETTE results are identical to those with the previous revision

  • Property svn:keywords set to Id
File size: 27.3 KB
RevLine 
[3443]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   !!----------------------------------------------------------------------
[9169]9   !!   p4z_sms        : Time loop of passive tracers sms
[3443]10   !!----------------------------------------------------------------------
[9169]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
[12377]19   USE p4zbc           ! External source of nutrients
[9169]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
[13286]27   USE prtctl          ! print control for debugging
[3443]28
29   IMPLICIT NONE
30   PRIVATE
31
[4990]32   PUBLIC   p4z_sms_init   ! called in p4zsms.F90
33   PUBLIC   p4z_sms        ! called in p4zsms.F90
[3443]34
[9169]35   INTEGER ::    numco2, numnut, numnit      ! logical unit for co2 budget
36   REAL(wp) ::   alkbudget, no3budget, silbudget, ferbudget, po4budget
[12276]37   REAL(wp) ::   xfact, xfact1, xfact2, xfact3
[3443]38
[9169]39   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     ! Array used to indicate negative tracer values
[5385]40
[12377]41   !! * Substitutions
42#  include "do_loop_substitute.h90"
[13237]43#  include "domzgr_substitute.h90"
[3443]44   !!----------------------------------------------------------------------
[10067]45   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
[10069]46   !! $Id$
[10068]47   !! Software governed by the CeCILL license (see ./LICENSE)
[3443]48   !!----------------------------------------------------------------------
49CONTAINS
50
[12377]51   SUBROUTINE p4z_sms( kt, Kbb, Kmm, Krhs )
[3443]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      !
[12377]63      INTEGER, INTENT( in ) ::   kt              ! ocean time-step index     
64      INTEGER, INTENT( in ) ::   Kbb, Kmm, Krhs  ! time level index
[3443]65      !!
[5385]66      INTEGER ::   ji, jj, jk, jnt, jn, jl
67      REAL(wp) ::  ztra
[3443]68      CHARACTER (len=25) :: charout
[12276]69      REAL(wp), ALLOCATABLE, DIMENSION(:,:    ) :: zw2d
70      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:  ) :: zw3d
71      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) ::   ztrdt   ! 4D workspace
72
[3443]73      !!---------------------------------------------------------------------
74      !
[9124]75      IF( ln_timing )   CALL timing_start('p4z_sms')
[3443]76      !
[4152]77      IF( kt == nittrc000 ) THEN
78        !
[5385]79        ALLOCATE( xnegtr(jpi,jpj,jpk) )
80        !
[9559]81        IF( .NOT. ln_rsttr ) THEN
[12377]82            CALL p4z_che( Kbb, Kmm )                  ! initialize the chemical constants
83            CALL ahini_for_at( hi, Kbb )              !  set PH at kt=nit000
[10382]84            t_oce_co2_flx_cum = 0._wp
[9559]85        ELSE
[12377]86            CALL p4z_rst( nittrc000, Kbb, Kmm,  'READ' )  !* read or initialize all required fields
[4152]87        ENDIF
88        !
89      ENDIF
90      !
[12377]91      IF( ln_pisdmp .AND. MOD( kt - 1, nn_pisdmp ) == 0 )   CALL p4z_dmp( kt, Kbb, Kmm )      ! Relaxation of some tracers
[3496]92      !
[12489]93      rfact = rDt_trc
[5385]94      !
[12276]95      ! trends computation initialisation
96      IF( l_trdtrc )  THEN
97         ALLOCATE( ztrdt(jpi,jpj,jpk,jp_pisces) )  !* store now fields before applying the Asselin filter
[12377]98         ztrdt(:,:,:,:)  = tr(:,:,:,:,Kmm)
[12276]99      ENDIF
100      !
101
[12377]102      IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + 1 ) ) THEN
[5385]103         rfactr  = 1. / rfact
[7646]104         rfact2  = rfact / REAL( nrdttrc, wp )
[5385]105         rfact2r = 1. / rfact2
106         xstep = rfact2 / rday         ! Time step duration for biology
[12276]107         xfact = 1.e+3 * rfact2r
[5385]108         IF(lwp) WRITE(numout,*) 
[12489]109         IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rn_Dt = ', rn_Dt
[5385]110         IF(lwp) write(numout,*) '    PISCES  Biology time step    rfact2 = ', rfact2
111         IF(lwp) WRITE(numout,*)
112      ENDIF
113
[12489]114      IF( l_1st_euler .OR. ln_top_euler ) THEN
[5385]115         DO jn = jp_pcs0, jp_pcs1              !   SMS on tracer without Asselin time-filter
[12377]116            tr(:,:,:,jn,Kbb) = tr(:,:,:,jn,Kmm)
[5385]117         END DO
118      ENDIF
119      !
[12377]120      IF( ll_bc )    CALL p4z_bc( kt, Kbb, Kmm, Krhs )   ! external sources of nutrients
[10222]121      !
122#if ! defined key_sed_off
[12377]123      CALL p4z_che(     Kbb, Kmm       ) ! computation of chemical constants
124      CALL p4z_int( kt, Kbb, Kmm       ) ! computation of various rates for biogeochemistry
[9559]125      !
[3443]126      DO jnt = 1, nrdttrc          ! Potential time splitting if requested
127         !
[12377]128         CALL p4z_bio( kt, jnt, Kbb, Kmm, Krhs )   ! Biology
129         CALL p4z_lys( kt, jnt, Kbb,      Krhs )   ! Compute CaCO3 saturation
130         CALL p4z_sed( kt, jnt, Kbb, Kmm, Krhs )   ! Surface and Bottom boundary conditions
131         CALL p4z_flx( kt, jnt, Kbb, Kmm, Krhs )   ! Compute surface fluxes
[3443]132         !
[7753]133         xnegtr(:,:,:) = 1.e0
[3443]134         DO jn = jp_pcs0, jp_pcs1
[13295]135            DO_3D( 1, 1, 1, 1, 1, jpk )
[12377]136               IF( ( tr(ji,jj,jk,jn,Kbb) + tr(ji,jj,jk,jn,Krhs) ) < 0.e0 ) THEN
137                  ztra             = ABS( tr(ji,jj,jk,jn,Kbb) ) / ( ABS( tr(ji,jj,jk,jn,Krhs) ) + rtrn )
138                  xnegtr(ji,jj,jk) = MIN( xnegtr(ji,jj,jk),  ztra )
139               ENDIF
140            END_3D
[5385]141         END DO
142         !                                ! where at least 1 tracer concentration becomes negative
143         !                                !
144         DO jn = jp_pcs0, jp_pcs1
[12377]145           tr(:,:,:,jn,Kbb) = tr(:,:,:,jn,Kbb) + xnegtr(:,:,:) * tr(:,:,:,jn,Krhs)
[5385]146         END DO
147        !
[12276]148        IF(  iom_use( 'INTdtAlk' ) .OR. iom_use( 'INTdtDIC' ) .OR. iom_use( 'INTdtFer' ) .OR.  &
149          &  iom_use( 'INTdtDIN' ) .OR. iom_use( 'INTdtDIP' ) .OR. iom_use( 'INTdtSil' ) )  THEN
150          !
151          ALLOCATE( zw3d(jpi,jpj,jpk), zw2d(jpi,jpj) )
152          zw3d(:,:,jpk) = 0.
153          DO jk = 1, jpkm1
[12377]154              zw3d(:,:,jk) = xnegtr(:,:,jk) * xfact * e3t(:,:,jk,Kmm) * tmask(:,:,jk)
[12276]155          ENDDO
156          !
157          zw2d(:,:) = 0.
158          DO jk = 1, jpkm1
[12377]159             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tr(:,:,jk,jptal,Krhs)
[12276]160          ENDDO
161          CALL iom_put( 'INTdtAlk', zw2d )
162          !
163          zw2d(:,:) = 0.
164          DO jk = 1, jpkm1
[12377]165             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tr(:,:,jk,jpdic,Krhs)
[12276]166          ENDDO
167          CALL iom_put( 'INTdtDIC', zw2d )
168          !
169          zw2d(:,:) = 0.
170          DO jk = 1, jpkm1
[12377]171             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * rno3 * ( tr(:,:,jk,jpno3,Krhs) + tr(:,:,jk,jpnh4,Krhs) )
[12276]172          ENDDO
173          CALL iom_put( 'INTdtDIN', zw2d )
174          !
175          zw2d(:,:) = 0.
176          DO jk = 1, jpkm1
[12377]177             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * po4r * tr(:,:,jk,jppo4,Krhs)
[12276]178          ENDDO
179          CALL iom_put( 'INTdtDIP', zw2d )
180          !
181          zw2d(:,:) = 0.
182          DO jk = 1, jpkm1
[12377]183             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tr(:,:,jk,jpfer,Krhs)
[12276]184          ENDDO
185          CALL iom_put( 'INTdtFer', zw2d )
186          !
187          zw2d(:,:) = 0.
188          DO jk = 1, jpkm1
[12377]189             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tr(:,:,jk,jpsil,Krhs)
[12276]190          ENDDO
191          CALL iom_put( 'INTdtSil', zw2d )
192          !
193          DEALLOCATE( zw3d, zw2d )
194        ENDIF
195        !
[5385]196         DO jn = jp_pcs0, jp_pcs1
[12377]197            tr(:,:,:,jn,Krhs) = 0._wp
[5385]198         END DO
[3443]199         !
[5385]200         IF( ln_top_euler ) THEN
201            DO jn = jp_pcs0, jp_pcs1
[12377]202               tr(:,:,:,jn,Kmm) = tr(:,:,:,jn,Kbb)
[5385]203            END DO
204         ENDIF
[3443]205      END DO
206      !
[5385]207      IF( l_trdtrc ) THEN
208         DO jn = jp_pcs0, jp_pcs1
[13030]209           ztrdt(:,:,:,jn) = ( tr(:,:,:,jn,Kbb) - ztrdt(:,:,:,jn) ) * rfactr 
[12377]210           CALL trd_trc( tr(:,:,:,jn,Krhs), jn, jptra_sms, kt, Kmm )   ! save trends
[5385]211         END DO
[12276]212         DEALLOCATE( ztrdt ) 
[5385]213      END IF
[10222]214#endif
[5385]215      !
[10222]216      IF( ln_sediment ) THEN 
[3443]217         !
[12377]218         CALL sed_model( kt, Kbb, Kmm, Krhs )     !  Main program of Sediment model
[3443]219         !
[10222]220         IF( ln_top_euler ) THEN
221            DO jn = jp_pcs0, jp_pcs1
[12377]222               tr(:,:,:,jn,Kmm) = tr(:,:,:,jn,Kbb)
[10222]223            END DO
224         ENDIF
225         !
[3443]226      ENDIF
227      !
[12377]228      IF( lrst_trc )  CALL p4z_rst( kt, Kbb, Kmm,  'WRITE' )           !* Write PISCES informations in restart file
[3443]229      !
[5385]230
[12377]231      IF( lk_iomput .OR. ln_check_mass )  CALL p4z_chk_mass( kt, Kmm ) ! Mass conservation checking
[3481]232
[12377]233      IF( lwm .AND. kt == nittrc000    )  CALL FLUSH( numonp )         ! flush output namelist PISCES
[3443]234      !
[9124]235      IF( ln_timing )  CALL timing_stop('p4z_sms')
[3481]236      !
[3443]237   END SUBROUTINE p4z_sms
238
[9124]239
[3443]240   SUBROUTINE p4z_sms_init
241      !!----------------------------------------------------------------------
242      !!                     ***  p4z_sms_init  *** 
243      !!
244      !! ** Purpose :   read PISCES namelist
245      !!
246      !! ** input   :   file 'namelist.trc.s' containing the following
247      !!             namelist: natext, natbio, natsms
248      !!----------------------------------------------------------------------
[9124]249      INTEGER :: ios                 ! Local integer output status for namelist read
250      !!
[7646]251      NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2, wsbio2max, wsbio2scale,    &
[10416]252         &                   ldocp, ldocz, lthet, no3rat3, po4rat3
[9124]253         !
[4148]254      NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp
[3531]255      NAMELIST/nampismass/ ln_check_mass
256      !!----------------------------------------------------------------------
[9169]257      !
258      IF(lwp) THEN
259         WRITE(numout,*)
260         WRITE(numout,*) 'p4z_sms_init : PISCES initialization'
261         WRITE(numout,*) '~~~~~~~~~~~~'
262      ENDIF
[3443]263
[4147]264      READ  ( numnatp_ref, nampisbio, IOSTAT = ios, ERR = 901)
[11536]265901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisbio in reference namelist' )
[4147]266      READ  ( numnatp_cfg, nampisbio, IOSTAT = ios, ERR = 902 )
[11536]267902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisbio in configuration namelist' )
[9169]268      IF(lwm) WRITE( numonp, nampisbio )
269      !
[3443]270      IF(lwp) THEN                         ! control print
[9169]271         WRITE(numout,*) '   Namelist : nampisbio'
272         WRITE(numout,*) '      frequency for the biology                 nrdttrc     =', nrdttrc
273         WRITE(numout,*) '      POC sinking speed                         wsbio       =', wsbio
274         WRITE(numout,*) '      half saturation constant for mortality    xkmort      =', xkmort 
[7646]275         IF( ln_p5z ) THEN
[9169]276            WRITE(numout,*) '      N/C in zooplankton                        no3rat3     =', no3rat3
277            WRITE(numout,*) '      P/C in zooplankton                        po4rat3     =', po4rat3
[7646]278         ENDIF
[9169]279         WRITE(numout,*) '      Fe/C in zooplankton                       ferat3      =', ferat3
280         WRITE(numout,*) '      Big particles sinking speed               wsbio2      =', wsbio2
281         WRITE(numout,*) '      Big particles maximum sinking speed       wsbio2max   =', wsbio2max
282         WRITE(numout,*) '      Big particles sinking speed length scale  wsbio2scale =', wsbio2scale
[7646]283         IF( ln_ligand ) THEN
284            IF( ln_p4z ) THEN
[9169]285               WRITE(numout,*) '      Phyto ligand production per unit doc           ldocp  =', ldocp
286               WRITE(numout,*) '      Zoo ligand production per unit doc             ldocz  =', ldocz
287               WRITE(numout,*) '      Proportional loss of ligands due to Fe uptake  lthet  =', lthet
[7646]288            ENDIF
289         ENDIF
[3443]290      ENDIF
291
292
[4147]293      READ  ( numnatp_ref, nampisdmp, IOSTAT = ios, ERR = 905)
[11536]294905   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisdmp in reference namelist' )
[4147]295      READ  ( numnatp_cfg, nampisdmp, IOSTAT = ios, ERR = 906 )
[11536]296906   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisdmp in configuration namelist' )
[9169]297      IF(lwm) WRITE( numonp, nampisdmp )
298      !
[3443]299      IF(lwp) THEN                         ! control print
300         WRITE(numout,*)
[9169]301         WRITE(numout,*) '   Namelist : nampisdmp --- relaxation to GLODAP'
302         WRITE(numout,*) '      Relaxation of tracer to glodap mean value   ln_pisdmp =', ln_pisdmp
303         WRITE(numout,*) '      Frequency of Relaxation                     nn_pisdmp =', nn_pisdmp
[3443]304      ENDIF
305
[4147]306      READ  ( numnatp_ref, nampismass, IOSTAT = ios, ERR = 907)
[11536]307907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampismass in reference namelist' )
[4147]308      READ  ( numnatp_cfg, nampismass, IOSTAT = ios, ERR = 908 )
[11536]309908   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampismass in configuration namelist' )
[9169]310      IF(lwm) WRITE( numonp, nampismass )
[4147]311
[3531]312      IF(lwp) THEN                         ! control print
[9169]313         WRITE(numout,*)
314         WRITE(numout,*) '   Namelist : nampismass  --- mass conservation checking'
315         WRITE(numout,*) '      Flag to check mass conservation of NO3/Si/TALK   ln_check_mass = ', ln_check_mass
[3531]316      ENDIF
[9124]317      !
[3443]318   END SUBROUTINE p4z_sms_init
319
[9124]320
[12377]321   SUBROUTINE p4z_rst( kt, Kbb, Kmm, cdrw )
[3443]322      !!---------------------------------------------------------------------
323      !!                   ***  ROUTINE p4z_rst  ***
324      !!
325      !!  ** Purpose : Read or write variables in restart file:
326      !!
327      !!  WRITE(READ) mode:
328      !!       kt        : number of time step since the begining of the experiment at the
329      !!                   end of the current(previous) run
330      !!---------------------------------------------------------------------
331      INTEGER         , INTENT(in) ::   kt         ! ocean time-step
[12377]332      INTEGER         , INTENT(in) ::   Kbb, Kmm   ! time level indices
[3443]333      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag
[9124]334      !!---------------------------------------------------------------------
[3443]335      !
336      IF( TRIM(cdrw) == 'READ' ) THEN
337         !
338         IF(lwp) WRITE(numout,*)
339         IF(lwp) WRITE(numout,*) ' p4z_rst : Read specific variables from pisces model '
340         IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~'
341         !
342         IF( iom_varid( numrtr, 'PH', ldstop = .FALSE. ) > 0 ) THEN
[13286]343            CALL iom_get( numrtr, jpdom_auto, 'PH' , hi(:,:,:)  )
[3443]344         ELSE
[12377]345            CALL p4z_che( Kbb, Kmm )                  ! initialize the chemical constants
346            CALL ahini_for_at( hi, Kbb )
[3443]347         ENDIF
[13286]348         CALL iom_get( numrtr, jpdom_auto, 'Silicalim', xksi(:,:) )
[3443]349         IF( iom_varid( numrtr, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN
[13286]350            CALL iom_get( numrtr, jpdom_auto, 'Silicamax' , xksimax(:,:)  )
[3443]351         ELSE
352            xksimax(:,:) = xksi(:,:)
353         ENDIF
354         !
[4996]355         IF( iom_varid( numrtr, 'tcflxcum', ldstop = .FALSE. ) > 0 ) THEN  ! cumulative total flux of carbon
356            CALL iom_get( numrtr, 'tcflxcum' , t_oce_co2_flx_cum  )
357         ELSE
358            t_oce_co2_flx_cum = 0._wp
359         ENDIF
360         !
[7646]361         IF( ln_p5z ) THEN
362            IF( iom_varid( numrtr, 'sized', ldstop = .FALSE. ) > 0 ) THEN
[13286]363               CALL iom_get( numrtr, jpdom_auto, 'sizep' , sizep(:,:,:)  )
364               CALL iom_get( numrtr, jpdom_auto, 'sizen' , sizen(:,:,:)  )
365               CALL iom_get( numrtr, jpdom_auto, 'sized' , sized(:,:,:)  )
[7646]366            ELSE
367               sizep(:,:,:) = 1.
368               sizen(:,:,:) = 1.
369               sized(:,:,:) = 1.
370            ENDIF
371        ENDIF
372        !
[3443]373      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN
374         IF( kt == nitrst ) THEN
375            IF(lwp) WRITE(numout,*)
376            IF(lwp) WRITE(numout,*) 'p4z_rst : write pisces restart file  kt =', kt
377            IF(lwp) WRITE(numout,*) '~~~~~~~'
378         ENDIF
379         CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:) )
380         CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) )
381         CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) )
[4996]382         CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum )
[7646]383         IF( ln_p5z ) THEN
[9909]384            CALL iom_rstput( kt, nitrst, numrtw, 'sizep', sizep(:,:,:) )
385            CALL iom_rstput( kt, nitrst, numrtw, 'sizen', sizen(:,:,:) )
[7646]386            CALL iom_rstput( kt, nitrst, numrtw, 'sized', sized(:,:,:) )
387         ENDIF
[3443]388      ENDIF
389      !
390   END SUBROUTINE p4z_rst
391
[9124]392
[12377]393   SUBROUTINE p4z_dmp( kt, Kbb, Kmm )
[3443]394      !!----------------------------------------------------------------------
395      !!                    ***  p4z_dmp  ***
396      !!
397      !! ** purpose  : Relaxation of some tracers
398      !!----------------------------------------------------------------------
399      !
[12377]400      INTEGER, INTENT( in )  ::     kt            ! time step
401      INTEGER, INTENT( in )  ::     Kbb, Kmm      ! time level indices
[3443]402      !
403      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. )
404      REAL(wp) ::  po4mean = 2.165     ! mean value of phosphates
405      REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate
406      REAL(wp) ::  silmean = 91.51     ! mean value of silicate
407      !
[5385]408      REAL(wp) :: zarea, zalksumn, zpo4sumn, zno3sumn, zsilsumn
409      REAL(wp) :: zalksumb, zpo4sumb, zno3sumb, zsilsumb
[3443]410      !!---------------------------------------------------------------------
411
412      IF(lwp)  WRITE(numout,*)
[3557]413      IF(lwp)  WRITE(numout,*) ' p4z_dmp : Restoring of nutrients at time-step kt = ', kt
[3443]414      IF(lwp)  WRITE(numout,*)
415
[10222]416      IF( cn_cfg == "ORCA" .OR. cn_cfg == "orca") THEN
[10213]417         IF( .NOT. lk_c1d ) THEN      ! ORCA configuration (not 1D) !
418            !                                                ! --------------------------- !
419            ! set total alkalinity, phosphate, nitrate & silicate
[10425]420            zarea          = 1._wp / glob_sum( 'p4zsms', cvol(:,:,:) ) * 1e6             
[3443]421
[12377]422            zalksumn = glob_sum( 'p4zsms', tr(:,:,:,jptal,Kmm) * cvol(:,:,:)  ) * zarea
423            zpo4sumn = glob_sum( 'p4zsms', tr(:,:,:,jppo4,Kmm) * cvol(:,:,:)  ) * zarea * po4r
424            zno3sumn = glob_sum( 'p4zsms', tr(:,:,:,jpno3,Kmm) * cvol(:,:,:)  ) * zarea * rno3
425            zsilsumn = glob_sum( 'p4zsms', tr(:,:,:,jpsil,Kmm) * cvol(:,:,:)  ) * zarea
[7753]426 
[10213]427            IF(lwp) WRITE(numout,*) '       TALKN mean : ', zalksumn
[12377]428            tr(:,:,:,jptal,Kmm) = tr(:,:,:,jptal,Kmm) * alkmean / zalksumn
[3443]429
[10213]430            IF(lwp) WRITE(numout,*) '       PO4N  mean : ', zpo4sumn
[12377]431            tr(:,:,:,jppo4,Kmm) = tr(:,:,:,jppo4,Kmm) * po4mean / zpo4sumn
[3443]432
[10213]433            IF(lwp) WRITE(numout,*) '       NO3N  mean : ', zno3sumn
[12377]434            tr(:,:,:,jpno3,Kmm) = tr(:,:,:,jpno3,Kmm) * no3mean / zno3sumn
[3443]435
[10213]436            IF(lwp) WRITE(numout,*) '       SiO3N mean : ', zsilsumn
[12377]437            tr(:,:,:,jpsil,Kmm) = MIN( 400.e-6,tr(:,:,:,jpsil,Kmm) * silmean / zsilsumn )
[10213]438            !
439            !
440            IF( .NOT. ln_top_euler ) THEN
[12377]441               zalksumb = glob_sum( 'p4zsms', tr(:,:,:,jptal,Kbb) * cvol(:,:,:)  ) * zarea
442               zpo4sumb = glob_sum( 'p4zsms', tr(:,:,:,jppo4,Kbb) * cvol(:,:,:)  ) * zarea * po4r
443               zno3sumb = glob_sum( 'p4zsms', tr(:,:,:,jpno3,Kbb) * cvol(:,:,:)  ) * zarea * rno3
444               zsilsumb = glob_sum( 'p4zsms', tr(:,:,:,jpsil,Kbb) * cvol(:,:,:)  ) * zarea
[7753]445 
[10213]446               IF(lwp) WRITE(numout,*) ' '
447               IF(lwp) WRITE(numout,*) '       TALKB mean : ', zalksumb
[12377]448               tr(:,:,:,jptal,Kbb) = tr(:,:,:,jptal,Kbb) * alkmean / zalksumb
[5385]449
[10213]450               IF(lwp) WRITE(numout,*) '       PO4B  mean : ', zpo4sumb
[12377]451               tr(:,:,:,jppo4,Kbb) = tr(:,:,:,jppo4,Kbb) * po4mean / zpo4sumb
[5385]452
[10213]453               IF(lwp) WRITE(numout,*) '       NO3B  mean : ', zno3sumb
[12377]454               tr(:,:,:,jpno3,Kbb) = tr(:,:,:,jpno3,Kbb) * no3mean / zno3sumb
[5385]455
[10213]456               IF(lwp) WRITE(numout,*) '       SiO3B mean : ', zsilsumb
[12377]457               tr(:,:,:,jpsil,Kbb) = MIN( 400.e-6,tr(:,:,:,jpsil,Kbb) * silmean / zsilsumb )
[10213]458           ENDIF
[5385]459        ENDIF
460        !
[3443]461      ENDIF
[5385]462        !
[3443]463   END SUBROUTINE p4z_dmp
464
465
[12377]466   SUBROUTINE p4z_chk_mass( kt, Kmm )
[3443]467      !!----------------------------------------------------------------------
468      !!                  ***  ROUTINE p4z_chk_mass  ***
469      !!
470      !! ** Purpose :  Mass conservation check
471      !!
472      !!---------------------------------------------------------------------
[5547]473      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index     
[12377]474      INTEGER, INTENT( in ) ::   Kmm     ! time level indices
[5547]475      REAL(wp)             ::  zrdenittot, zsdenittot, znitrpottot
[5385]476      CHARACTER(LEN=100)   ::   cltxt
477      INTEGER :: jk
[9125]478      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zwork
[5385]479      !!----------------------------------------------------------------------
480      !
[3443]481      IF( kt == nittrc000 ) THEN
[8533]482         xfact1 = rfact2r * 12. / 1.e15 * ryyss    ! conversion molC/kt --> PgC/yr
483         xfact2 = 1.e+3 * rno3 * 14. / 1.e12 * ryyss   ! conversion molC/l/s ----> TgN/m3/yr
484         xfact3 = 1.e+3 * rfact2r * rno3   ! conversion molC/l/kt ----> molN/m3/s
[3451]485         IF( ln_check_mass .AND. lwp) THEN      !   Open budget file of NO3, ALK, Si, Fer
[3496]486            CALL ctl_opn( numco2, 'carbon.budget'  , 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
487            CALL ctl_opn( numnut, 'nutrient.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
[5385]488            CALL ctl_opn( numnit, 'nitrogen.budget', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
489            cltxt='time-step   Alkalinity        Nitrate        Phosphorus         Silicate           Iron'
490            IF( lwp ) WRITE(numnut,*)  TRIM(cltxt)
491            IF( lwp ) WRITE(numnut,*) 
[3443]492         ENDIF
493      ENDIF
494
[4996]495      IF( iom_use( "pno3tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
496         !   Compute the budget of NO3, ALK, Si, Fer
[7646]497         IF( ln_p4z ) THEN
[12377]498            zwork(:,:,:) =    tr(:,:,:,jpno3,Kmm) + tr(:,:,:,jpnh4,Kmm)                      &
499               &          +   tr(:,:,:,jpphy,Kmm) + tr(:,:,:,jpdia,Kmm)                      &
500               &          +   tr(:,:,:,jppoc,Kmm) + tr(:,:,:,jpgoc,Kmm)  + tr(:,:,:,jpdoc,Kmm)  &       
501               &          +   tr(:,:,:,jpzoo,Kmm) + tr(:,:,:,jpmes,Kmm) 
[7646]502        ELSE
[12377]503            zwork(:,:,:) =    tr(:,:,:,jpno3,Kmm) + tr(:,:,:,jpnh4,Kmm) + tr(:,:,:,jpnph,Kmm)   &
504               &          +   tr(:,:,:,jpndi,Kmm) + tr(:,:,:,jpnpi,Kmm)                      & 
505               &          +   tr(:,:,:,jppon,Kmm) + tr(:,:,:,jpgon,Kmm) + tr(:,:,:,jpdon,Kmm)   &
506               &          + ( tr(:,:,:,jpzoo,Kmm) + tr(:,:,:,jpmes,Kmm) ) * no3rat3 
[7646]507        ENDIF
508        !
[10425]509        no3budget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  ) 
[7646]510        no3budget = no3budget / areatot
511        CALL iom_put( "pno3tot", no3budget )
[4996]512      ENDIF
513      !
[5385]514      IF( iom_use( "ppo4tot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
[7646]515         IF( ln_p4z ) THEN
[12377]516            zwork(:,:,:) =    tr(:,:,:,jppo4,Kmm)                                         &
517               &          +   tr(:,:,:,jpphy,Kmm) + tr(:,:,:,jpdia,Kmm)                      &
518               &          +   tr(:,:,:,jppoc,Kmm) + tr(:,:,:,jpgoc,Kmm)  + tr(:,:,:,jpdoc,Kmm)  &       
519               &          +   tr(:,:,:,jpzoo,Kmm) + tr(:,:,:,jpmes,Kmm) 
[7646]520        ELSE
[12377]521            zwork(:,:,:) =    tr(:,:,:,jppo4,Kmm) + tr(:,:,:,jppph,Kmm)                      &
522               &          +   tr(:,:,:,jppdi,Kmm) + tr(:,:,:,jpppi,Kmm)                      & 
523               &          +   tr(:,:,:,jppop,Kmm) + tr(:,:,:,jpgop,Kmm) + tr(:,:,:,jpdop,Kmm)   &
524               &          + ( tr(:,:,:,jpzoo,Kmm) + tr(:,:,:,jpmes,Kmm) ) * po4rat3 
[7646]525        ENDIF
526        !
[10425]527        po4budget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  ) 
[7646]528        po4budget = po4budget / areatot
529        CALL iom_put( "ppo4tot", po4budget )
[5385]530      ENDIF
531      !
532      IF( iom_use( "psiltot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
[12377]533         zwork(:,:,:) =  tr(:,:,:,jpsil,Kmm) + tr(:,:,:,jpgsi,Kmm) + tr(:,:,:,jpdsi,Kmm) 
[4996]534         !
[10425]535         silbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  ) 
[4996]536         silbudget = silbudget / areatot
537         CALL iom_put( "psiltot", silbudget )
538      ENDIF
539      !
[5385]540      IF( iom_use( "palktot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
[12377]541         zwork(:,:,:) =  tr(:,:,:,jpno3,Kmm) * rno3 + tr(:,:,:,jptal,Kmm) + tr(:,:,:,jpcal,Kmm) * 2.             
[4996]542         !
[10425]543         alkbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )         !
[4996]544         alkbudget = alkbudget / areatot
545         CALL iom_put( "palktot", alkbudget )
546      ENDIF
547      !
[5385]548      IF( iom_use( "pfertot" ) .OR. ( ln_check_mass .AND. kt == nitend )  ) THEN
[12377]549         zwork(:,:,:) =   tr(:,:,:,jpfer,Kmm) + tr(:,:,:,jpnfe,Kmm) + tr(:,:,:,jpdfe,Kmm)   &
550            &         +   tr(:,:,:,jpbfe,Kmm) + tr(:,:,:,jpsfe,Kmm)                      &
551            &         + ( tr(:,:,:,jpzoo,Kmm) + tr(:,:,:,jpmes,Kmm) )  * ferat3   
[3496]552         !
[10425]553         ferbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  ) 
[3496]554         ferbudget = ferbudget / areatot
[4996]555         CALL iom_put( "pfertot", ferbudget )
[3496]556      ENDIF
[4996]557      !
[5385]558      ! Global budget of N SMS : denitrification in the water column and in the sediment
559      !                          nitrogen fixation by the diazotrophs
560      ! --------------------------------------------------------------------------------
561      IF( iom_use( "tnfix" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
[10425]562         znitrpottot  = glob_sum ( 'p4zsms', nitrpot(:,:,:) * nitrfix * cvol(:,:,:) )
[8533]563         CALL iom_put( "tnfix"  , znitrpottot * xfact3 )  ! Global  nitrogen fixation molC/l  to molN/m3
[5385]564      ENDIF
565      !
566      IF( iom_use( "tdenit" ) .OR.  ( ln_check_mass .AND. kt == nitend )  ) THEN
[10425]567         zrdenittot = glob_sum ( 'p4zsms', denitr(:,:,:) * rdenit * xnegtr(:,:,:) * cvol(:,:,:) )
568         zsdenittot = glob_sum ( 'p4zsms', sdenit(:,:) * e1e2t(:,:) * tmask(:,:,1) )
[8533]569         CALL iom_put( "tdenit" , ( zrdenittot + zsdenittot ) * xfact3 )  ! Total denitrification molC/l to molN/m3
[5385]570      ENDIF
571      !
[4996]572      IF( ln_check_mass .AND. kt == nitend ) THEN   ! Compute the budget of NO3, ALK, Si, Fer
[10425]573         t_atm_co2_flx  = t_atm_co2_flx / glob_sum( 'p4zsms', e1e2t(:,:) )
[5385]574         t_oce_co2_flx  = t_oce_co2_flx         * xfact1 * (-1 )
575         tpp            = tpp           * 1000. * xfact1
576         t_oce_co2_exp  = t_oce_co2_exp * 1000. * xfact1
[4996]577         IF( lwp ) WRITE(numco2,9000) ndastp, t_atm_co2_flx, t_oce_co2_flx, tpp, t_oce_co2_exp
[5385]578         IF( lwp ) WRITE(numnut,9100) ndastp, alkbudget        * 1.e+06, &
[4996]579             &                                no3budget * rno3 * 1.e+06, &
[5385]580             &                                po4budget * po4r * 1.e+06, &
[4996]581             &                                silbudget        * 1.e+06, &
582             &                                ferbudget        * 1.e+09
[5385]583         !
584         IF( lwp ) WRITE(numnit,9200) ndastp, znitrpottot * xfact2  , &
[9124]585            &                             zrdenittot  * xfact2  , &
586            &                             zsdenittot  * xfact2
[4996]587      ENDIF
588      !
[3496]589 9000  FORMAT(i8,f10.5,e18.10,f10.5,f10.5)
[5385]590 9100  FORMAT(i8,5e18.10)
591 9200  FORMAT(i8,3f10.5)
[3443]592       !
593   END SUBROUTINE p4z_chk_mass
594
595   !!======================================================================
596END MODULE p4zsms 
Note: See TracBrowser for help on using the repository browser.