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.
Changeset 15548 for NEMO/branches/2021/ticket2632_r14588_theta_sbcblk/src/TOP/PISCES/SED/sedbtb.F90 – NEMO

Ignore:
Timestamp:
2021-11-28T18:59:49+01:00 (3 years ago)
Author:
gsamson
Message:

update branch to the head of the trunk (r15547); ticket #2632

Location:
NEMO/branches/2021/ticket2632_r14588_theta_sbcblk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/ticket2632_r14588_theta_sbcblk

    • Property svn:externals
      •  

        old new  
        99 
        1010# SETTE 
        11 ^/utils/CI/sette@14244        sette 
         11^/utils/CI/sette@HEAD        sette 
         12 
  • NEMO/branches/2021/ticket2632_r14588_theta_sbcblk/src/TOP/PISCES/SED/sedbtb.F90

    r10222 r15548  
    66   !! * Modules used 
    77   USE sed     ! sediment global variable 
     8   USE sed_oce 
    89   USE sedmat  ! linear system of equations 
     10   USE sedinorg 
     11   USE sedorg 
     12   USE sedini 
    913   USE lib_mpp         ! distribued memory computing library 
    1014 
     
    3135      !!        !  06-04 (C. Ethe)  Re-organization 
    3236      !!---------------------------------------------------------------------- 
    33       !!* Arguments 
    34       INTEGER, INTENT(in) ::  kt              ! time step 
    35  
     37      !! * Arguments 
     38      INTEGER, INTENT(in)  :: kt   ! time step 
    3639      ! * local variables 
    3740      INTEGER :: ji, jk, js 
    38       REAL(wp), DIMENSION(jpoce,jpksedm1,jpsol) ::  zsol  !   solution 
     41      REAL(wp), DIMENSION(jpoce,jpksed,jpsol) ::  zrearat  !   solution 
     42      REAL(wp) :: zsolid1, zsolid2, zsolid3, zsumtot, zlimo2 
    3943      !------------------------------------------------------------------------ 
    4044 
     
    4246 
    4347      IF( kt == nitsed000 ) THEN 
    44          IF (lwp) WRITE(numsed,*) ' sed_btb : Bioturbation  ' 
     48         IF (lwp) WRITE(numsed,*) ' sed_btb : bioturbation of solid and adsorbed species  ' 
    4549         IF (lwp) WRITE(numsed,*) ' ' 
    4650      ENDIF 
    4751 
     52 
    4853      ! Initializations 
    4954      !---------------- 
    50       zsol(:,:,:) = 0. 
     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 
    5161 
    5262      ! right hand side of coefficient matrix 
    5363      !-------------------------------------- 
    54       DO js = 1, jpsol 
    55          DO jk = 1, jpksedm1 
    56             DO ji = 1, jpoce 
    57                zsol(ji,jk,js) = solcp(ji,jk+1,js) 
    58             ENDDO 
    59          ENDDO 
    60       ENDDO 
     64      CALL sed_mat_btbi( jpksed, jpsol, solcp, zrearat(:,:,:), dtsed ) 
    6165 
    62       CALL sed_mat( jpsol, jpoce, jpksedm1, zsol, dtsed / 2.0 ) 
     66      DO ji = 1, jpoce 
    6367 
     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 
    6476 
    65       ! store solution of the tridiagonal system 
    66       !------------------------ 
    67       DO js = 1, jpsol 
    68          DO jk = 1, jpksedm1 
    69             DO ji = 1, jpoce 
    70                solcp(ji,jk+1,js) = zsol(ji,jk,js) 
    71             ENDDO 
    72          ENDDO 
    73       ENDDO 
     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 ) 
    74111 
    75112      IF( ln_timing )  CALL timing_stop('sed_btb') 
Note: See TracChangeset for help on using the changeset viewer.