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.
sedbtb.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/sedbtb.F90 @ 15297

Last change on this file since 15297 was 15297, checked in by aumont, 2 years ago

major update of the sediment module

  • Property svn:keywords set to Id
File size: 4.0 KB
Line 
1MODULE sedbtb
2   !!======================================================================
3   !!              ***  MODULE  sedbtb  ***
4   !!    Sediment : bioturbation of the solid components
5   !!=====================================================================
6   !! * Modules used
7   USE sed     ! sediment global variable
8   USE sed_oce
9   USE sedmat  ! linear system of equations
10   USE sedinorg
11   USE sedorg
12   USE sedini
13   USE lib_mpp         ! distribued memory computing library
14
15   IMPLICIT NONE
16   PRIVATE
17
18   PUBLIC sed_btb
19
20
21   !! $Id$
22CONTAINS
23   
24   SUBROUTINE sed_btb( kt )
25      !!---------------------------------------------------------------------
26      !!                  ***  ROUTINE sed_btb  ***
27      !!
28      !! ** Purpose :  performs bioturbation of the solid sediment components
29      !!
30      !! ** Method  :  ``diffusion'' of solid sediment components.
31      !!
32      !!   History :
33      !!        !  98-08 (E. Maier-Reimer, Christoph Heinze )  Original code
34      !!        !  04-10 (N. Emprin, M. Gehlen ) F90
35      !!        !  06-04 (C. Ethe)  Re-organization
36      !!----------------------------------------------------------------------
37      !! * Arguments
38      INTEGER, INTENT(in)  :: kt   ! time step
39      ! * local variables
40      INTEGER :: ji, jk, js
41      REAL(wp), DIMENSION(jpoce,jpksed,jpsol) ::  zrearat  !   solution
42      REAL(wp) :: zsolid1, zsolid2, zsolid3, zsumtot, zlimo2
43      !------------------------------------------------------------------------
44
45      IF( ln_timing )  CALL timing_start('sed_btb')
46
47      IF( kt == nitsed000 ) THEN
48         IF (lwp) WRITE(numsed,*) ' sed_btb : bioturbation of solid and adsorbed species  '
49         IF (lwp) WRITE(numsed,*) ' '
50      ENDIF
51
52
53      ! Initializations
54      !----------------
55      zrearat = 0.
56
57      ! Remineralization rates of the different POC pools
58      zrearat(:,:,jspoc) = -reac_pocl
59      zrearat(:,:,jspos) = -reac_pocs
60      zrearat(:,:,jspor) = -reac_pocr
61
62      ! right hand side of coefficient matrix
63      !--------------------------------------
64      CALL sed_mat_btbi( jpsol, solcp, zrearat(:,:,:), dtsed )
65
66      DO ji = 1, jpoce
67
68         zsumtot = 0.
69         DO jk = 2, jpksed
70            zsolid1 = volc(ji,jk,jspoc) * solcp(ji,jk,jspoc)
71            zsolid2 = volc(ji,jk,jspos) * solcp(ji,jk,jspos)
72            zsolid3 = volc(ji,jk,jspor) * solcp(ji,jk,jspor)
73            rearatpom(ji,jk)  = ( reac_pocl * zsolid1 + reac_pocs * zsolid2 + reac_pocr * zsolid3 )
74            zsumtot = zsumtot + rearatpom(ji,jk) * volw3d(ji,jk) * 1.e-3 * 86400. * 365. * 1E3
75         END DO
76
77         !    4/ Computation of the bioturbation coefficient
78         !       This parameterization is taken from Archer et al. (2002)
79         ! --------------------------------------------------------------
80         zlimo2   = max(0.01, pwcp(ji,1,jwoxy) / (pwcp(ji,1,jwoxy) + 20.E-6) )
81         db(ji,:) = dbiot * zsumtot**0.85 * zlimo2 / (365.0 * 86400.0)
82
83         ! ------------------------------------------------------
84         !    Vertical variations of the bioturbation coefficient
85         ! ------------------------------------------------------
86         IF (ln_btbz) THEN
87            DO jk = 1, jpksed
88                  db(ji,jk) = db(ji,jk) * exp( -(profsedw(jk) / dbtbzsc)**2 )
89            END DO
90         ELSE
91            DO jk = 1, jpksed
92               IF (profsedw(jk) > dbtbzsc) THEN
93                  db(ji,jk) = 0.0
94               ENDIF
95            END DO
96         ENDIF
97
98         ! Computation of the bioirrigation factor (from Archer, MUDS model)
99         irrig(ji,:) = 0.0
100         IF (ln_irrig) THEN
101            DO jk = 1, jpksed
102               irrig(ji,jk) = ( 7.63752 - 7.4465 * exp( -0.89603 * zsumtot ) ) * zlimo2
103               irrig(ji,jk) = irrig(ji,jk) * exp( -(profsedw(jk) / xirrzsc) )
104            END DO
105         ENDIF
106      END DO
107 
108      ! CALL inorganic and organic slow redow/chemistry processes
109      ! ---------------------------------------------------------
110      CALL sed_inorg( kt )
111
112      IF( ln_timing )  CALL timing_stop('sed_btb')
113
114   END SUBROUTINE sed_btb
115
116END MODULE sedbtb
Note: See TracBrowser for help on using the repository browser.