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.
sedinorg.F90 in NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/SED – NEMO

source: NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/TOP/PISCES/SED/sedinorg.F90 @ 15075

Last change on this file since 15075 was 15075, checked in by aumont, 3 years ago

major update of the sediment module

File size: 5.3 KB
Line 
1MODULE sedinorg
2   !!======================================================================
3   !!              ***  MODULE  sedinorg  ***
4   !!    Sediment : dissolution and reaction in pore water of
5   !!               inorganic species
6   !!=====================================================================
7   !! * Modules used
8   USE sed     ! sediment global variable
9   USE sed_oce
10   USE sedini
11   USE lib_mpp         ! distribued memory computing library
12   USE lib_fortran
13
14   IMPLICIT NONE
15   PRIVATE
16
17   PUBLIC sed_inorg
18
19   !! $Id: seddsr.F90 5215 2015-04-15 16:11:56Z nicolasmartin $
20CONTAINS
21   
22   SUBROUTINE sed_inorg( kt )
23      !!----------------------------------------------------------------------
24      !!                   ***  ROUTINE sed_inorg  ***
25      !!
26      !!  ** Purpose :  computes pore water dissolution and reaction
27      !!
28      !!  ** Methode :  implicit simultaneous computation of undersaturation
29      !!               resulting from diffusive pore water transport and chemical
30      !!               pore water reactions. Solid material is consumed according
31      !!               to redissolution and remineralisation
32      !!
33      !!  ** Remarks :
34      !!              - undersaturation : deviation from saturation concentration
35      !!              - reaction rate   : sink of undersaturation from dissolution
36      !!                                 of solid material
37      !!
38      !!   History :
39      !!        !  98-08 (E. Maier-Reimer, Christoph Heinze )  Original code
40      !!        !  04-10 (N. Emprin, M. Gehlen ) f90
41      !!        !  06-04 (C. Ethe)  Re-organization
42      !!        !  19-08 (O. Aumont) Debugging and improvement of the model
43      !!----------------------------------------------------------------------
44      !! Arguments
45      INTEGER, INTENT(in)  :: kt   ! time step
46      ! --- local variables
47      INTEGER   ::  ji,jk          ! dummy looop indices
48      REAL(wp)  ::  zsieq
49      REAL(wp)  ::  zsolid1, zreasat
50      REAL(wp)  ::  zsatur, zsatur2, znusil, zsolcpcl, zsolcpsi, zexcess
51      !!
52      !!----------------------------------------------------------------------
53
54      IF( ln_timing )  CALL timing_start('sed_inorg')
55
56      IF( kt == nitsed000 ) THEN
57         IF (lwp) WRITE(numsed,*) ' sed_inorg : Dissolution of CaCO3 and BSi  '
58         IF (lwp) WRITE(numsed,*) ' '
59      ENDIF
60!
61      DO ji = 1, jpoce
62         ! -----------------------------------------------
63         ! Computation of Si solubility
64         ! Param of Ridgwell et al. 2002
65         ! -----------------------------------------------
66
67         zsolcpcl = 0.0
68         zsolcpsi = 0.0
69         DO jk = 1, jpksed
70            zsolcpsi = zsolcpsi + solcp(ji,jk,jsopal) * vols3d(ji,jk)
71            zsolcpcl = zsolcpcl + solcp(ji,jk,jsclay) * vols3d(ji,jk)
72         END DO
73         zsolcpsi = MAX( zsolcpsi, rtrn )
74         zsieq = sieqs(ji) * MAX(0.25, 1.0 - (0.045 * zsolcpcl / zsolcpsi )**0.58 )
75
76         !----------------------------------------------------------
77         ! 5.  Beginning of  Pore Water diffusion and solid reaction
78         !---------------------------------------------------------
79     
80         !-----------------------------------------------------------------------------
81         ! For jk=2,jpksed, and for couple
82         !  1 : jwsil/jsopal  ( SI/Opal )
83         !  2 : jsclay/jsclay ( clay/clay )
84         !  3 : jwoxy/jspoc   ( O2/POC )
85         !  reaction rate is a function of solid=concentration in solid reactif in [mol/l]
86         !  and undersaturation in [mol/l].
87         !  Solid weight fractions should be in ie [mol/l])
88         !  second member and solution are in zundsat variable
89         !-------------------------------------------------------------------------
90         DO jk = 2, jpksed
91            zsolid1 = volc(ji,jk,jsopal) * solcp(ji,jk,jsopal)
92            zsatur = MAX(0., ( zsieq - pwcp(ji,jk,jwsil) ) / zsieq )
93            zsatur2 = (1.0 + temp(ji) / 400.0 )**37
94            znusil = ( 0.225 * ( 1.0 + temp(ji) / 15.) * zsatur + 0.775 * zsatur2 * zsatur**9.25 )
95            solcp(ji,jk,jsopal) = solcp(ji,jk,jsopal) - reac_sil * znusil * dtsed * solcp(ji,jk,jsopal)
96            pwcp(ji,jk,jwsil) = pwcp(ji,jk,jwsil) + reac_sil * znusil * dtsed * zsolid1
97         END DO
98      END DO
99
100      !---------------------------------------------------------------
101      ! Performs CaCO3 particle deposition and redissolution (indice 9)
102      !--------------------------------------------------------------
103
104      ! computes co3por from the updated pwcp concentrations (note [co3por] = mol/l)
105      ! *densSW(l)**2 converts aksps [mol2/kg sol2] into [mol2/l2] to get [undsat] in [mol/l]
106      DO ji = 1, jpoce
107         saturco3(ji,:) = 1.0 - co3por(ji,:) * calcon2(ji) / ( aksps(ji) * densSW(ji) * densSW(ji) + rtrn ) 
108         DO jk = 2, jpksed
109            zsolid1 = volc(ji,jk,jscal) * solcp(ji,jk,jscal)
110            zexcess = MAX( 0., saturco3(ji,jk) ) 
111            zreasat = reac_cal * dtsed * zexcess * zsolid1
112            solcp(ji,jk,jscal) = solcp(ji,jk,jscal) - zreasat / volc(ji,jk,jscal)
113            ! For DIC
114            pwcp(ji,jk,jwdic)  = pwcp(ji,jk,jwdic) + zreasat
115            ! For alkalinity
116            pwcp(ji,jk,jwalk)  = pwcp(ji,jk,jwalk) + 2.0 * zreasat
117         END DO
118      END DO
119
120      IF( ln_timing )  CALL timing_stop('sed_inorg')
121!     
122   END SUBROUTINE sed_inorg
123
124END MODULE sedinorg
Note: See TracBrowser for help on using the repository browser.