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

source: NEMO/branches/2019/fix_sn_cfctl_ticket2328/src/TOP/PISCES/P4Z/p4zsink.F90 @ 11872

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

Branch 2019/fix_sn_cfctl_ticket2328. See #2328. Replacement of ln_ctl and activation of full functionality with
sn_cfctl structure. These changes rename structure components l_mppout and l_mpptop as l_prtctl and l_prttrc
and introduce l_glochk to activate former ln_ctl code in stpctl.F90 to perform global location of min and max
checks. Also added is l_allon which can be used to activate all output (much like the former ln_ctl). If l_allon
is .false. then l_config decides whether or not the suboptions are used.

   sn_cfctl%l_glochk = .FALSE.    ! Range sanity checks are local (F) or global (T). Set T for debugging only
   sn_cfctl%l_allon  = .FALSE.    ! IF T activate all options. If F deactivate all unless l_config is T
   sn_cfctl%l_config = .TRUE.     ! IF .true. then control which reports are written with the remaining options

Note, these changes pass SETTE tests but all references to ln_ctl need to be removed from the sette scripts.

  • Property svn:keywords set to Id
File size: 10.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      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d
65      REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zw2d
66      !!---------------------------------------------------------------------
67      !
68      IF( ln_timing )   CALL timing_start('p4z_sink')
69
70      ! Initialization of some global variables
71      ! ---------------------------------------
72      prodpoc(:,:,:) = 0.
73      conspoc(:,:,:) = 0.
74      prodgoc(:,:,:) = 0.
75      consgoc(:,:,:) = 0.
76
77      !
78      !    Sinking speeds of detritus is increased with depth as shown
79      !    by data and from the coagulation theory
80      !    -----------------------------------------------------------
81      DO jk = 1, jpkm1
82         DO jj = 1, jpj
83            DO ji = 1,jpi
84               zmax  = MAX( heup_01(ji,jj), hmld(ji,jj) )
85               zfact = MAX( 0., gdepw_n(ji,jj,jk+1) - zmax ) / wsbio2scale
86               wsbio4(ji,jj,jk) = wsbio2 + MAX(0., ( wsbio2max - wsbio2 )) * zfact
87            END DO
88         END DO
89      END DO
90
91      ! limit the values of the sinking speeds to avoid numerical instabilities 
92      wsbio3(:,:,:) = wsbio
93
94      !
95      !  Initializa to zero all the sinking arrays
96      !   -----------------------------------------
97      sinking (:,:,:) = 0.e0
98      sinking2(:,:,:) = 0.e0
99      sinkcal (:,:,:) = 0.e0
100      sinkfer (:,:,:) = 0.e0
101      sinksil (:,:,:) = 0.e0
102      sinkfer2(:,:,:) = 0.e0
103
104      !   Compute the sedimentation term using p4zsink2 for all the sinking particles
105      !   -----------------------------------------------------
106      CALL trc_sink( kt, wsbio3, sinking , jppoc, rfact2 )
107      CALL trc_sink( kt, wsbio3, sinkfer , jpsfe, rfact2 )
108      CALL trc_sink( kt, wsbio4, sinking2, jpgoc, rfact2 )
109      CALL trc_sink( kt, wsbio4, sinkfer2, jpbfe, rfact2 )
110      CALL trc_sink( kt, wsbio4, sinksil , jpgsi, rfact2 )
111      CALL trc_sink( kt, wsbio4, sinkcal , jpcal, rfact2 )
112
113      IF( ln_p5z ) THEN
114         sinkingn (:,:,:) = 0.e0
115         sinking2n(:,:,:) = 0.e0
116         sinkingp (:,:,:) = 0.e0
117         sinking2p(:,:,:) = 0.e0
118
119         !   Compute the sedimentation term using p4zsink2 for all the sinking particles
120         !   -----------------------------------------------------
121         CALL trc_sink( kt, wsbio3, sinkingn , jppon, rfact2 )
122         CALL trc_sink( kt, wsbio3, sinkingp , jppop, rfact2 )
123         CALL trc_sink( kt, wsbio4, sinking2n, jpgon, rfact2 )
124         CALL trc_sink( kt, wsbio4, sinking2p, jpgop, rfact2 )
125      ENDIF
126
127     ! Total carbon export per year
128     IF( iom_use( "tcexp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  &
129        &   t_oce_co2_exp = glob_sum( 'p4zsink', ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) )
130     !
131     IF( lk_iomput ) THEN
132       IF( knt == nrdttrc ) THEN
133          ALLOCATE( zw2d(jpi,jpj), zw3d(jpi,jpj,jpk) )
134          zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s
135          !
136          IF( iom_use( "EPC100" ) )  THEN
137              zw2d(:,:) = ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * zfact * tmask(:,:,1) ! Export of carbon at 100m
138              CALL iom_put( "EPC100"  , zw2d )
139          ENDIF
140          IF( iom_use( "EPFE100" ) )  THEN
141              zw2d(:,:) = ( sinkfer(:,:,ik100) + sinkfer2(:,:,ik100) ) * zfact * tmask(:,:,1) ! Export of iron at 100m
142              CALL iom_put( "EPFE100"  , zw2d )
143          ENDIF
144          IF( iom_use( "EPCAL100" ) )  THEN
145              zw2d(:,:) = sinkcal(:,:,ik100) * zfact * tmask(:,:,1) ! Export of calcite at 100m
146              CALL iom_put( "EPCAL100"  , zw2d )
147          ENDIF
148          IF( iom_use( "EPSI100" ) )  THEN
149              zw2d(:,:) =  sinksil(:,:,ik100) * zfact * tmask(:,:,1) ! Export of bigenic silica at 100m
150              CALL iom_put( "EPSI100"  , zw2d )
151          ENDIF
152          IF( iom_use( "EXPC" ) )  THEN
153              zw3d(:,:,:) = ( sinking(:,:,:) + sinking2(:,:,:) ) * zfact * tmask(:,:,:) ! Export of carbon in the water column
154              CALL iom_put( "EXPC"  , zw3d )
155          ENDIF
156          IF( iom_use( "EXPFE" ) )  THEN
157              zw3d(:,:,:) = ( sinkfer(:,:,:) + sinkfer2(:,:,:) ) * zfact * tmask(:,:,:) ! Export of iron
158              CALL iom_put( "EXPFE"  , zw3d )
159          ENDIF
160          IF( iom_use( "EXPCAL" ) )  THEN
161              zw3d(:,:,:) = sinkcal(:,:,:) * zfact * tmask(:,:,:) ! Export of calcite
162              CALL iom_put( "EXPCAL"  , zw3d )
163          ENDIF
164          IF( iom_use( "EXPSI" ) )  THEN
165              zw3d(:,:,:) = sinksil(:,:,:) * zfact * tmask(:,:,:) ! Export of bigenic silica
166              CALL iom_put( "EXPSI"  , zw3d )
167          ENDIF
168          IF( iom_use( "tcexp" ) )  CALL iom_put( "tcexp" , t_oce_co2_exp * zfact )   ! molC/s
169          !
170          DEALLOCATE( zw2d, zw3d )
171        ENDIF
172      ENDIF
173      !
174      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging)
175         WRITE(charout, FMT="('sink')")
176         CALL prt_ctl_trc_info(charout)
177         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm)
178      ENDIF
179      !
180      IF( ln_timing )   CALL timing_stop('p4z_sink')
181      !
182   END SUBROUTINE p4z_sink
183
184
185   SUBROUTINE p4z_sink_init
186      !!----------------------------------------------------------------------
187      !!                  ***  ROUTINE p4z_sink_init  ***
188      !!----------------------------------------------------------------------
189      INTEGER :: jk
190      !!----------------------------------------------------------------------
191      !
192      ik100 = 10        !  last level where depth less than 100 m
193      DO jk = jpkm1, 1, -1
194         IF( gdept_1d(jk) > 100. )  ik100 = jk - 1
195      END DO
196      IF (lwp) WRITE(numout,*)
197      IF (lwp) WRITE(numout,*) ' Level corresponding to 100m depth ',  ik100 + 1
198      IF (lwp) WRITE(numout,*)
199      !
200      t_oce_co2_exp = 0._wp
201      !
202   END SUBROUTINE p4z_sink_init
203
204   INTEGER FUNCTION p4z_sink_alloc()
205      !!----------------------------------------------------------------------
206      !!                     ***  ROUTINE p4z_sink_alloc  ***
207      !!----------------------------------------------------------------------
208      INTEGER :: ierr(2)
209      !!----------------------------------------------------------------------
210      !
211      ierr(:) = 0
212      !
213      ALLOCATE( sinking(jpi,jpj,jpk) , sinking2(jpi,jpj,jpk)                    ,     &               
214         &      sinkcal(jpi,jpj,jpk) , sinksil (jpi,jpj,jpk)                    ,     &               
215         &      sinkfer2(jpi,jpj,jpk)                                           ,     &               
216         &      sinkfer(jpi,jpj,jpk)                                            , STAT=ierr(1) )               
217         !
218      IF( ln_p5z    ) ALLOCATE( sinkingn(jpi,jpj,jpk), sinking2n(jpi,jpj,jpk)   ,     &
219         &                      sinkingp(jpi,jpj,jpk), sinking2p(jpi,jpj,jpk)   , STAT=ierr(2) )
220      !
221      p4z_sink_alloc = MAXVAL( ierr )
222      IF( p4z_sink_alloc /= 0 ) CALL ctl_stop( 'STOP', 'p4z_sink_alloc : failed to allocate arrays.' )
223      !
224   END FUNCTION p4z_sink_alloc
225   
226   !!======================================================================
227END MODULE p4zsink
Note: See TracBrowser for help on using the repository browser.