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/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zsink.F90 @ 13233

Last change on this file since 13233 was 13233, checked in by aumont, 4 years ago

update of the PISCES comments

  • Property svn:keywords set to Id
File size: 11.0 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_trc      !  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   !!----------------------------------------------------------------------
45   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
46   !! $Id$
47   !! Software governed by the CeCILL license (see ./LICENSE)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE p4z_sink ( kt, knt )
52      !!---------------------------------------------------------------------
53      !!                     ***  ROUTINE p4z_sink  ***
54      !!
55      !! ** Purpose :   Compute vertical flux of particulate matter due to
56      !!                gravitational sinking.
57      !!
58      !! ** Method  : - An external advection subroutine is called to compute
59      !!                the impact of sinking on the particles. The tracers
60      !!                concentrations are updated in this subroutine which
61      !!                is mandatory to deal with negative concentrations
62      !!---------------------------------------------------------------------
63      INTEGER, INTENT(in) :: kt, knt
64      INTEGER  ::   ji, jj, jk
65      CHARACTER (len=25) :: charout
66      REAL(wp) :: zmax, zfact
67      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d
68      REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zw2d
69      !!---------------------------------------------------------------------
70      !
71      IF( ln_timing )   CALL timing_start('p4z_sink')
72
73      ! Initialization of some global variables
74      ! ---------------------------------------
75      prodpoc(:,:,:) = 0.
76      conspoc(:,:,:) = 0.
77      prodgoc(:,:,:) = 0.
78      consgoc(:,:,:) = 0.
79
80      ! Sinking speeds of big detritus is increased with depth as shown
81      ! by data and from the coagulation theory. This is controled by
82      ! wsbio2max and wsbio2scale. If wsbio2max is set to wsbio2, then
83      ! sinking speed is constant with depth.
84      ! CaCO3 and bSi are supposed to sink at the big particles speed
85      ! due to their high density
86      ! ---------------------------------------------------------------
87      DO jk = 1, jpkm1
88         DO jj = 1, jpj
89            DO ji = 1,jpi
90               zmax  = MAX( heup_01(ji,jj), hmld(ji,jj) )
91               zfact = MAX( 0., gdepw_n(ji,jj,jk+1) - zmax ) / wsbio2scale
92               wsbio4(ji,jj,jk) = wsbio2 + MAX(0., ( wsbio2max - wsbio2 )) * zfact
93            END DO
94         END DO
95      END DO
96
97      ! Sinking speed of the small particles is always constant
98      wsbio3(:,:,:) = wsbio
99
100      ! Initialize to zero all the sinking arrays
101      ! -----------------------------------------
102      sinking (:,:,:) = 0.e0
103      sinking2(:,:,:) = 0.e0
104      sinkcal (:,:,:) = 0.e0
105      sinkfer (:,:,:) = 0.e0
106      sinksil (:,:,:) = 0.e0
107      sinkfer2(:,:,:) = 0.e0
108
109      ! Compute the sedimentation term using trc_sink for all the sinking particles
110      ! ---------------------------------------------------------------------------
111      CALL trc_sink( kt, wsbio3, sinking , jppoc, rfact2 )
112      CALL trc_sink( kt, wsbio3, sinkfer , jpsfe, rfact2 )
113      CALL trc_sink( kt, wsbio4, sinking2, jpgoc, rfact2 )
114      CALL trc_sink( kt, wsbio4, sinkfer2, jpbfe, rfact2 )
115      CALL trc_sink( kt, wsbio4, sinksil , jpgsi, rfact2 )
116      CALL trc_sink( kt, wsbio4, sinkcal , jpcal, rfact2 )
117
118      ! PISCES-QUOTA part
119      IF( ln_p5z ) THEN
120         sinkingn (:,:,:) = 0.e0
121         sinking2n(:,:,:) = 0.e0
122         sinkingp (:,:,:) = 0.e0
123         sinking2p(:,:,:) = 0.e0
124
125         ! Compute the sedimentation term using trc_sink for all the sinking particles
126         ! ---------------------------------------------------------------------------
127         CALL trc_sink( kt, wsbio3, sinkingn , jppon, rfact2 )
128         CALL trc_sink( kt, wsbio3, sinkingp , jppop, rfact2 )
129         CALL trc_sink( kt, wsbio4, sinking2n, jpgon, rfact2 )
130         CALL trc_sink( kt, wsbio4, sinking2p, jpgop, rfact2 )
131      ENDIF
132
133     ! Total carbon export per year
134     IF( iom_use( "tcexp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  &
135        &   t_oce_co2_exp = glob_sum( 'p4zsink', ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) )
136     !
137     IF( lk_iomput ) THEN
138       IF( knt == nrdttrc ) THEN
139          ALLOCATE( zw2d(jpi,jpj), zw3d(jpi,jpj,jpk) )
140          zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s
141          !
142          IF( iom_use( "EPC100" ) )  THEN
143              zw2d(:,:) = ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * zfact * tmask(:,:,1) ! Export of carbon at 100m
144              CALL iom_put( "EPC100"  , zw2d )
145          ENDIF
146          IF( iom_use( "EPFE100" ) )  THEN
147              zw2d(:,:) = ( sinkfer(:,:,ik100) + sinkfer2(:,:,ik100) ) * zfact * tmask(:,:,1) ! Export of iron at 100m
148              CALL iom_put( "EPFE100"  , zw2d )
149          ENDIF
150          IF( iom_use( "EPCAL100" ) )  THEN
151              zw2d(:,:) = sinkcal(:,:,ik100) * zfact * tmask(:,:,1) ! Export of calcite at 100m
152              CALL iom_put( "EPCAL100"  , zw2d )
153          ENDIF
154          IF( iom_use( "EPSI100" ) )  THEN
155              zw2d(:,:) =  sinksil(:,:,ik100) * zfact * tmask(:,:,1) ! Export of bigenic silica at 100m
156              CALL iom_put( "EPSI100"  , zw2d )
157          ENDIF
158          IF( iom_use( "EXPC" ) )  THEN
159              zw3d(:,:,:) = ( sinking(:,:,:) + sinking2(:,:,:) ) * zfact * tmask(:,:,:) ! Export of carbon in the water column
160              CALL iom_put( "EXPC"  , zw3d )
161          ENDIF
162          IF( iom_use( "EXPFE" ) )  THEN
163              zw3d(:,:,:) = ( sinkfer(:,:,:) + sinkfer2(:,:,:) ) * zfact * tmask(:,:,:) ! Export of iron
164              CALL iom_put( "EXPFE"  , zw3d )
165          ENDIF
166          IF( iom_use( "EXPCAL" ) )  THEN
167              zw3d(:,:,:) = sinkcal(:,:,:) * zfact * tmask(:,:,:) ! Export of calcite
168              CALL iom_put( "EXPCAL"  , zw3d )
169          ENDIF
170          IF( iom_use( "EXPSI" ) )  THEN
171              zw3d(:,:,:) = sinksil(:,:,:) * zfact * tmask(:,:,:) ! Export of bigenic silica
172              CALL iom_put( "EXPSI"  , zw3d )
173          ENDIF
174          IF( iom_use( "tcexp" ) )  CALL iom_put( "tcexp" , t_oce_co2_exp * zfact )   ! molC/s
175          !
176          DEALLOCATE( zw2d, zw3d )
177        ENDIF
178      ENDIF
179      !
180      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
181         WRITE(charout, FMT="('sink')")
182         CALL prt_ctl_trc_info(charout)
183         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
184      ENDIF
185      !
186      IF( ln_timing )   CALL timing_stop('p4z_sink')
187      !
188   END SUBROUTINE p4z_sink
189
190
191   SUBROUTINE p4z_sink_init
192      !!----------------------------------------------------------------------
193      !!                  ***  ROUTINE p4z_sink_init  ***
194      !!
195      !! ** Purpose :   Initialization of sinking parameters
196      !!
197      !! ** Method  :   
198      !!
199      !! ** input   :   
200      !!----------------------------------------------------------------------
201      INTEGER :: jk
202      !!----------------------------------------------------------------------
203      !
204      ik100 = 10        !  last level where depth less than 100 m
205      DO jk = jpkm1, 1, -1
206         IF( gdept_1d(jk) > 100. )  ik100 = jk - 1
207      END DO
208      IF (lwp) WRITE(numout,*)
209      IF (lwp) WRITE(numout,*) ' Level corresponding to 100m depth ',  ik100 + 1
210      IF (lwp) WRITE(numout,*)
211      !
212      t_oce_co2_exp = 0._wp
213      !
214   END SUBROUTINE p4z_sink_init
215
216   INTEGER FUNCTION p4z_sink_alloc()
217      !!----------------------------------------------------------------------
218      !!                     ***  ROUTINE p4z_sink_alloc  ***
219      !!----------------------------------------------------------------------
220      INTEGER :: ierr(2)
221      !!----------------------------------------------------------------------
222      !
223      ierr(:) = 0
224      !
225      ALLOCATE( sinking(jpi,jpj,jpk) , sinking2(jpi,jpj,jpk)                    ,     &               
226         &      sinkcal(jpi,jpj,jpk) , sinksil (jpi,jpj,jpk)                    ,     &               
227         &      sinkfer2(jpi,jpj,jpk)                                           ,     &               
228         &      sinkfer(jpi,jpj,jpk)                                            , STAT=ierr(1) )               
229         !
230      IF( ln_p5z    ) ALLOCATE( sinkingn(jpi,jpj,jpk), sinking2n(jpi,jpj,jpk)   ,     &
231         &                      sinkingp(jpi,jpj,jpk), sinking2p(jpi,jpj,jpk)   , STAT=ierr(2) )
232      !
233      p4z_sink_alloc = MAXVAL( ierr )
234      IF( p4z_sink_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_sink_alloc : failed to allocate arrays.' )
235      !
236   END FUNCTION p4z_sink_alloc
237   
238   !!======================================================================
239END MODULE p4zsink
Note: See TracBrowser for help on using the repository browser.