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

source: NEMO/trunk/src/TOP/PISCES/P4Z/p4zsink.F90

Last change on this file was 15459, checked in by cetlod, 2 years ago

Various bug fixes and more comments in PISCES routines ; sette test OK in debug mode, nn_hls=1/2, with tiling ; run.stat unchanged ; of course tracer.stat different

  • Property svn:keywords set to Id
File size: 10.2 KB
Line 
1MODULE p4zsink
2   !!======================================================================
3   !!                         ***  MODULE p4zsink  ***
4   !! TOP :  PISCES  vertical flux of particulate matter due to
5   !!        gravitational sinking
6   !!        This module is the same for both PISCES and PISCES-QUOTA
7   !!======================================================================
8   !! History :   1.0  !  2004     (O. Aumont) Original code
9   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
10   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Change aggregation formula
11   !!             3.5  !  2012-07  (O. Aumont) Introduce potential time-splitting
12   !!             4.0  !  2019     (O. Aumont) an external subroutine is called
13   !!                                          to compute the impact of sinking
14   !!----------------------------------------------------------------------
15   !!   p4z_sink       :  Compute vertical flux of particulate matter due to gravitational sinking
16   !!   p4z_sink_init  :  Unitialisation of sinking speed parameters
17   !!   p4z_sink_alloc :  Allocate sinking speed variables
18   !!----------------------------------------------------------------------
19   USE oce_trc         !  shared variables between ocean and passive tracers
20   USE trc             !  passive tracers common variables
21   USE sms_pisces      !  PISCES Source Minus Sink variables
22   USE trcsink         !  General routine to compute sedimentation
23   USE prtctl          !  print control for debugging
24   USE iom             !  I/O manager
25   USE lib_mpp
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   p4z_sink         ! called in p4zbio.F90
31   PUBLIC   p4z_sink_init    ! called in trcini_pisces.F90
32   PUBLIC   p4z_sink_alloc   ! called in trcini_pisces.F90
33
34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinking, sinking2  !: POC sinking fluxes
35   !                                                          !  (different meanings depending on the parameterization)
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkingn, sinking2n  !: PON sinking fluxes
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkingp, sinking2p  !: POP sinking fluxes
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkcal, sinksil   !: CaCO3 and BSi sinking fluxes
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkfer            !: Small BFe sinking fluxes
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkfer2           !: Big iron sinking fluxes
41
42   INTEGER  :: ik100
43
44   !! * Substitutions
45#  include "do_loop_substitute.h90"
46#  include "domzgr_substitute.h90"
47   !!----------------------------------------------------------------------
48   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
49   !! $Id$
50   !! Software governed by the CeCILL license (see ./LICENSE)
51   !!----------------------------------------------------------------------
52CONTAINS
53
54   SUBROUTINE p4z_sink ( kt, knt, Kbb, Kmm, Krhs )
55      !!---------------------------------------------------------------------
56      !!                     ***  ROUTINE p4z_sink  ***
57      !!
58      !! ** Purpose :   Compute vertical flux of particulate matter due to
59      !!                gravitational sinking.
60      !!
61      !! ** Method  : - An external advection subroutine is called to compute
62      !!                the impact of sinking on the particles. The tracers
63      !!                concentrations are updated in this subroutine which
64      !!                is mandatory to deal with negative concentrations
65      !!---------------------------------------------------------------------
66      INTEGER, INTENT(in) :: kt, knt
67      INTEGER, INTENT(in) :: Kbb, Kmm, Krhs  ! time level indices
68      INTEGER  ::   ji, jj, jk
69      CHARACTER (len=25) :: charout
70      REAL(wp) :: zmax, zfact
71      !!---------------------------------------------------------------------
72      !
73      IF( ln_timing )   CALL timing_start('p4z_sink')
74
75      ! Initialization of some global variables
76      ! ---------------------------------------
77      prodpoc(:,:,:) = 0.
78      conspoc(:,:,:) = 0.
79      prodgoc(:,:,:) = 0.
80      consgoc(:,:,:) = 0.
81
82      ! Sinking speeds of big detritus is increased with depth as shown
83      ! by data and from the coagulation theory. This is controled by
84      ! wsbio2max and wsbio2scale. If wsbio2max is set to wsbio2, then
85      ! sinking speed is constant with depth.
86      ! CaCO3 and bSi are supposed to sink at the big particles speed
87      ! due to their high density
88      ! ---------------------------------------------------------------
89      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1)
90         zmax  = MAX( heup_01(ji,jj), hmld(ji,jj) )
91         zfact = MAX( 0., gdepw(ji,jj,jk+1,Kmm) - zmax ) / wsbio2scale
92         wsbio4(ji,jj,jk) = wsbio2 + MAX(0., ( wsbio2max - wsbio2 )) * zfact
93      END_3D
94
95      ! Sinking speed of the small particles is always constant
96      wsbio3(:,:,:) = wsbio
97
98      ! Initialize to zero all the sinking arrays
99      ! -----------------------------------------
100      sinking (:,:,:) = 0.e0
101      sinking2(:,:,:) = 0.e0
102      sinkcal (:,:,:) = 0.e0
103      sinkfer (:,:,:) = 0.e0
104      sinksil (:,:,:) = 0.e0
105      sinkfer2(:,:,:) = 0.e0
106
107      ! Compute the sedimentation term using trc_sink for all the sinking particles
108      ! ---------------------------------------------------------------------------
109      CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinking , jppoc, rfact2 )
110      CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkfer , jpsfe, rfact2 )
111      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2, jpgoc, rfact2 )
112      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinkfer2, jpbfe, rfact2 )
113      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinksil , jpgsi, rfact2 )
114      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinkcal , jpcal, rfact2 )
115
116      ! PISCES-QUOTA part
117      IF( ln_p5z ) THEN
118         sinkingn (:,:,:) = 0.e0
119         sinking2n(:,:,:) = 0.e0
120         sinkingp (:,:,:) = 0.e0
121         sinking2p(:,:,:) = 0.e0
122
123         ! Compute the sedimentation term using trc_sink for all the sinking particles
124         ! ---------------------------------------------------------------------------
125         CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkingn , jppon, rfact2 )
126         CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkingp , jppop, rfact2 )
127         CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2n, jpgon, rfact2 )
128         CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2p, jpgop, rfact2 )
129      ENDIF
130
131     ! Total carbon export per year
132     IF( iom_use( "tcexp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  &
133        &   t_oce_co2_exp = glob_sum( 'p4zsink', ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) )
134     !
135     IF( lk_iomput .AND.  knt == nrdttrc ) THEN
136       zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s
137       !
138       CALL iom_put( "EPC100"  , ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * zfact * tmask(:,:,1) ) ! Export of carbon at 100m
139       CALL iom_put( "EPFE100" , ( sinkfer(:,:,ik100) + sinkfer2(:,:,ik100) ) * zfact * tmask(:,:,1) ) ! Export of iron at 100m
140       CALL iom_put( "EPCAL100", sinkcal(:,:,ik100) * zfact * tmask(:,:,1) )      ! Export of calcite at 100m
141       CALL iom_put( "EPSI100" , sinksil(:,:,ik100) * zfact * tmask(:,:,1) )          ! Export of bigenic silica at 100m
142       CALL iom_put( "EXPC"    , ( sinking(:,:,:) + sinking2(:,:,:) ) * zfact * tmask(:,:,:) ) ! Export of carbon in the water column
143       CALL iom_put( "EXPFE"   , ( sinkfer(:,:,:) + sinkfer2(:,:,:) ) * zfact * tmask(:,:,:) ) ! Export of iron 
144       CALL iom_put( "EXPCAL"  , sinkcal(:,:,:) * zfact * tmask(:,:,:) )      ! Export of calcite
145       CALL iom_put( "EXPSI"   , sinksil(:,:,:) * zfact * tmask(:,:,:) )      ! Export of bigenic silica
146       CALL iom_put( "tcexp"   , t_oce_co2_exp * zfact )   ! molC/s
147       !
148      ENDIF
149      !
150      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
151         WRITE(charout, FMT="('sink')")
152         CALL prt_ctl_info( charout, cdcomp = 'top' )
153         CALL prt_ctl(tab4d_1=tr(:,:,:,:,Krhs), mask1=tmask, clinfo=ctrcnm)
154      ENDIF
155      !
156      IF( ln_timing )   CALL timing_stop('p4z_sink')
157      !
158   END SUBROUTINE p4z_sink
159
160
161   SUBROUTINE p4z_sink_init
162      !!----------------------------------------------------------------------
163      !!                  ***  ROUTINE p4z_sink_init  ***
164      !!
165      !! ** Purpose :   Initialization of sinking parameters
166      !!
167      !! ** Method  :   
168      !!
169      !! ** input   :   
170      !!----------------------------------------------------------------------
171      INTEGER :: jk
172      !!----------------------------------------------------------------------
173      !
174      ik100 = 10        !  last level where depth less than 100 m
175      DO jk = jpkm1, 1, -1
176         IF( gdept_1d(jk) > 100. )  ik100 = jk - 1
177      END DO
178      IF (lwp) WRITE(numout,*)
179      IF (lwp) WRITE(numout,*) ' Level corresponding to 100m depth ',  ik100 + 1
180      IF (lwp) WRITE(numout,*)
181      !
182      t_oce_co2_exp = 0._wp
183      !
184   END SUBROUTINE p4z_sink_init
185
186   INTEGER FUNCTION p4z_sink_alloc()
187      !!----------------------------------------------------------------------
188      !!                     ***  ROUTINE p4z_sink_alloc  ***
189      !!----------------------------------------------------------------------
190      INTEGER :: ierr(2)
191      !!----------------------------------------------------------------------
192      !
193      ierr(:) = 0
194      !
195      ALLOCATE( sinking(jpi,jpj,jpk) , sinking2(jpi,jpj,jpk)                    ,     &               
196         &      sinkcal(jpi,jpj,jpk) , sinksil (jpi,jpj,jpk)                    ,     &               
197         &      sinkfer2(jpi,jpj,jpk)                                           ,     &               
198         &      sinkfer(jpi,jpj,jpk)                                            , STAT=ierr(1) )               
199         !
200      IF( ln_p5z    ) ALLOCATE( sinkingn(jpi,jpj,jpk), sinking2n(jpi,jpj,jpk)   ,     &
201         &                      sinkingp(jpi,jpj,jpk), sinking2p(jpi,jpj,jpk)   , STAT=ierr(2) )
202      !
203      p4z_sink_alloc = MAXVAL( ierr )
204      IF( p4z_sink_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_sink_alloc : failed to allocate arrays.' )
205      !
206   END FUNCTION p4z_sink_alloc
207   
208   !!======================================================================
209END MODULE p4zsink
Note: See TracBrowser for help on using the repository browser.