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 @ 15127

Last change on this file since 15127 was 15127, checked in by cetlod, 3 years ago

dev_PISCO : merge with trunk@15119

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