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_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z – NEMO

source: NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zsink.F90 @ 13662

Last change on this file since 13662 was 13662, checked in by clem, 3 years ago

update to almost r4.0.4

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