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/seddta.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/seddta.F90

    r13295 r15548  
    88   USE sed 
    99   USE sedarr 
     10   USE sedini 
    1011   USE phycst, ONLY : rday 
    1112   USE iom 
     
    1920 
    2021   !! *  Module variables 
    21    REAL(wp) ::  rsecday  ! number of second per a day 
    2222   REAL(wp) ::  conv2    ! [kg/m2/month]-->[g/cm2/s] ( 1 month has 30 days ) 
    2323 
     
    2525#  include "do_loop_substitute.h90" 
    2626#  include "domzgr_substitute.h90" 
    27    !! $Id$ 
     27 
    2828CONTAINS 
    2929 
     
    4646 
    4747      !! Arguments 
    48       INTEGER, INTENT(in) ::  kt         ! time-step 
    49       INTEGER, INTENT(in) ::  Kbb, Kmm  ! time level indices 
     48      INTEGER, INTENT( in ) ::   kt    ! time-step 
     49      INTEGER, INTENT( in ) ::   Kbb, Kmm ! time level indices 
    5050 
    5151      !! * Local declarations 
     
    5353 
    5454      REAL(wp), DIMENSION(jpoce) :: zdtap, zdtag 
    55       REAL(wp), DIMENSION(jpi,jpj) :: zwsbio4, zwsbio3 
     55      REAL(wp), DIMENSION(jpi,jpj) :: zwsbio4, zwsbio3, zddust 
    5656      REAL(wp) :: zf0, zf1, zf2, zkapp, zratio, zdep 
     57      REAL(wp) :: zzf0, zf0s, zf0b, zzf1, zf1s, zf1b, zzf2, zf2s, zf2b 
    5758 
    5859      !---------------------------------------------------------------------- 
     
    7778         IF (lwp) WRITE(numsed,*) ' sed_dta : Sediment fields' 
    7879         dtsed = rDt_trc 
    79          rsecday = 60.* 60. * 24. 
    80 !         conv2   = 1.0e+3 / ( 1.0e+4 * rsecday * 30. ) 
    8180         conv2 = 1.0e+3 /  1.0e+4  
    82          rdtsed(2:jpksed) = dtsed / ( denssol * por1(2:jpksed) ) 
    8381      ENDIF 
    8482 
     
    8684      zdtap(:)    = 0.  
    8785      zdtag(:)    = 0.   
     86      zddust(:,:) = 0.0 
    8887 
    8988      ! reading variables 
     
    9695      !    ----------------------------------------------------------- 
    9796      IF (ln_sediment_offline) THEN 
    98          DO_2D( 1, 1, 1, 1 ) 
     97         DO_2D( 0, 0, 0, 0 ) 
    9998            ikt = mbkt(ji,jj) 
    10099            zwsbio4(ji,jj) = wsbio2 / rday 
     
    102101         END_2D 
    103102      ELSE 
    104          DO_2D( 1, 1, 1, 1 ) 
     103         DO_2D( 0, 0, 0, 0 ) 
    105104            ikt = mbkt(ji,jj) 
    106105            zdep = e3t(ji,jj,ikt,Kmm) / rDt_trc 
     
    111110 
    112111      trc_data(:,:,:) = 0. 
    113       DO_2D( 1, 1, 1, 1 ) 
     112      DO_2D( 0, 0, 0, 0 ) 
    114113         ikt = mbkt(ji,jj) 
    115          IF ( tmask(ji,jj,ikt) == 1 ) THEN 
    116             trc_data(ji,jj,1)   = tr(ji,jj,ikt,jpsil,Kbb) 
    117             trc_data(ji,jj,2)   = tr(ji,jj,ikt,jpoxy,Kbb) 
    118             trc_data(ji,jj,3)   = tr(ji,jj,ikt,jpdic,Kbb) 
    119             trc_data(ji,jj,4)   = tr(ji,jj,ikt,jpno3,Kbb) / 7.625 
    120             trc_data(ji,jj,5)   = tr(ji,jj,ikt,jppo4,Kbb) / 122. 
    121             trc_data(ji,jj,6)   = tr(ji,jj,ikt,jptal,Kbb) 
    122             trc_data(ji,jj,7)   = tr(ji,jj,ikt,jpnh4,Kbb) / 7.625 
    123             trc_data(ji,jj,8)   = 0.0 
    124             trc_data(ji,jj,9)   = 28.0E-3 
    125             trc_data(ji,jj,10)  = tr(ji,jj,ikt,jpfer,Kbb) 
    126             trc_data(ji,jj,11 ) = MIN(tr(ji,jj,ikt,jpgsi,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3 
    127             trc_data(ji,jj,12 ) = MIN(tr(ji,jj,ikt,jppoc,Kbb), 1E-4) * zwsbio3(ji,jj) * 1E3 
    128             trc_data(ji,jj,13 ) = MIN(tr(ji,jj,ikt,jpgoc,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3 
    129             trc_data(ji,jj,14)  = MIN(tr(ji,jj,ikt,jpcal,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3 
    130             trc_data(ji,jj,15)  = ts(ji,jj,ikt,jp_tem,Kmm) 
    131             trc_data(ji,jj,16)  = ts(ji,jj,ikt,jp_sal,Kmm) 
    132             trc_data(ji,jj,17 ) = ( tr(ji,jj,ikt,jpsfe,Kbb) * zwsbio3(ji,jj) + tr(ji,jj,ikt,jpbfe,Kbb)  & 
    133             &                     * zwsbio4(ji,jj)  ) * 1E3 / ( trc_data(ji,jj,12 ) + trc_data(ji,jj,13 ) + rtrn ) 
    134             trc_data(ji,jj,17 ) = MIN(1E-3, trc_data(ji,jj,17 ) ) 
     114         IF ( tmask(ji,jj,ikt) == 1.0 ) THEN 
     115            trc_data(ji,jj,jwsil) = tr(ji,jj,ikt,jpsil,Kbb) 
     116            trc_data(ji,jj,jwoxy) = tr(ji,jj,ikt,jpoxy,Kbb) 
     117            trc_data(ji,jj,jwdic) = tr(ji,jj,ikt,jpdic,Kbb) 
     118            trc_data(ji,jj,jwno3) = tr(ji,jj,ikt,jpno3,Kbb) * redNo3 / redC 
     119            trc_data(ji,jj,jwpo4) = tr(ji,jj,ikt,jppo4,Kbb) / redC 
     120            trc_data(ji,jj,jwalk) = tr(ji,jj,ikt,jptal,Kbb)  
     121            trc_data(ji,jj,jwnh4) = tr(ji,jj,ikt,jpnh4,Kbb) * redNo3 / redC  
     122            trc_data(ji,jj,jwh2s) = 0.0 
     123            trc_data(ji,jj,jwso4) = 0.14 * ts(ji,jj,ikt,jp_sal,Kmm) / 1.80655 / 96.062 
     124            trc_data(ji,jj,jwfe2) = tr(ji,jj,ikt,jpfer,Kbb) 
     125            trc_data(ji,jj,jwlgw) = 1E-9 
     126            trc_data(ji,jj,12 )   = MIN(tr(ji,jj,ikt,jpgsi,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3 
     127            trc_data(ji,jj,13 )   = MIN(tr(ji,jj,ikt,jppoc,Kbb), 1E-4) * zwsbio3(ji,jj) * 1E3 
     128            trc_data(ji,jj,14 )   = MIN(tr(ji,jj,ikt,jpgoc,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3 
     129            trc_data(ji,jj,15)    = MIN(tr(ji,jj,ikt,jpcal,Kbb), 1E-4) * zwsbio4(ji,jj) * 1E3 
     130            trc_data(ji,jj,16)    = ts(ji,jj,ikt,jp_tem,Kmm) 
     131            trc_data(ji,jj,17)    = ts(ji,jj,ikt,jp_sal,Kmm) 
     132            trc_data(ji,jj,18 )   = ( tr(ji,jj,ikt,jpsfe,Kbb) * zwsbio3(ji,jj) + tr(ji,jj,ikt,jpbfe,Kbb)  & 
     133            &                       * zwsbio4(ji,jj)  ) * 1E3 / ( trc_data(ji,jj,13 ) + trc_data(ji,jj,14 ) + rtrn ) 
     134            trc_data(ji,jj,18 )   = MIN(1E-3, trc_data(ji,jj,18 ) ) 
    135135         ENDIF 
    136136      END_2D 
     
    141141         CALL pack_arr ( jpoce,  pwcp_dta(1:jpoce,jw), trc_data(1:jpi,1:jpj,jw), iarroce(1:jpoce) ) 
    142142      END DO 
     143 
    143144      !  Solid components :  
    144145      !----------------------- 
    145146      !  Sinking fluxes for OPAL in mol.m-2.s-1 ; conversion in mol.cm-2.s-1 
    146       CALL pack_arr ( jpoce, rainrm_dta(1:jpoce,jsopal), trc_data(1:jpi,1:jpj,11), iarroce(1:jpoce) )  
     147      CALL pack_arr ( jpoce, rainrm_dta(1:jpoce,jsopal), trc_data(1:jpi,1:jpj,12), iarroce(1:jpoce) )  
    147148      rainrm_dta(1:jpoce,jsopal) = rainrm_dta(1:jpoce,jsopal) * 1e-4 
     149 
    148150      !  Sinking fluxes for POC in mol.m-2.s-1 ; conversion in mol.cm-2.s-1 
    149       CALL pack_arr ( jpoce, zdtap(1:jpoce), trc_data(1:jpi,1:jpj,12) , iarroce(1:jpoce) )       
    150       CALL pack_arr ( jpoce, zdtag(1:jpoce), trc_data(1:jpi,1:jpj,13) , iarroce(1:jpoce) ) 
     151      CALL pack_arr ( jpoce, zdtap(1:jpoce), trc_data(1:jpi,1:jpj,13) , iarroce(1:jpoce) )       
     152      CALL pack_arr ( jpoce, zdtag(1:jpoce), trc_data(1:jpi,1:jpj,14) , iarroce(1:jpoce) ) 
    151153      DO ji = 1, jpoce 
    152 !        zkapp  = MIN( (1.0 - 0.02 ) * reac_poc, 3731.0 * max(100.0, zkbot(ji) )**(-1.011) / ( 365.0 * 24.0 * 3600.0 ) ) 
    153 !        zkapp   = MIN( 0.98 * reac_poc, 100.0 * max(100.0, zkbot(ji) )**(-0.6) / ( 365.0 * 24.0 * 3600.0 ) ) 
    154 !        zratio = ( ( 1.0 - 0.02 ) * reac_poc + 0.02 * reac_poc * 0. - zkapp) / ( ( 0.02 - 1.0 ) * reac_poc / 100. - 0.02 * reac_poc * 0. + zkapp ) 
    155 !        zf1    = ( 0.02 * (reac_poc - reac_poc * 0.) + zkapp - reac_poc ) / ( reac_poc / 100. - reac_poc ) 
    156 !        zf1    = MIN(0.98, MAX(0., zf1 ) ) 
    157          zf1    = 0.48 
    158          zf0    = 1.0 - 0.02 - zf1 
    159          zf2    = 0.02 
    160          rainrm_dta(ji,jspoc) =   ( zdtap(ji) +  zdtag(ji) ) * 1e-4 * zf0 
    161          rainrm_dta(ji,jspos) =   ( zdtap(ji) +  zdtag(ji) ) * 1e-4 * zf1 
    162          rainrm_dta(ji,jspor) =   ( zdtap(ji) +  zdtag(ji) ) * 1e-4 * zf2 
     154         zzf2 = 2E-2 
     155         zzf1 = 0.3 
     156         zzf0 = 1.0 - zzf1 - zzf2 
     157         zf0s = zzf0 
     158         zf1s = zzf1 
     159         zf2s = 1.0 - zf1s - zf0s 
     160         zf0b = zzf0 
     161         zf1b = zzf1 
     162         zf2b = 1.0 - zf1b - zf0b 
     163         rainrm_dta(ji,jspoc) =   ( zdtap(ji) * zf0s +  zdtag(ji) * zf0b ) * 1e-4 
     164         rainrm_dta(ji,jspos) =   ( zdtap(ji) * zf1s +  zdtag(ji) * zf1b ) * 1e-4 
     165         rainrm_dta(ji,jspor) =   ( zdtap(ji) * zf2s +  zdtag(ji) * zf2b ) * 1e-4 
    163166      END DO 
     167 
    164168      !  Sinking fluxes for Calcite in mol.m-2.s-1 ; conversion in mol.cm-2.s-1 
    165       CALL pack_arr ( jpoce,  rainrm_dta(1:jpoce,jscal), trc_data(1:jpi,1:jpj,14), iarroce(1:jpoce) ) 
     169      CALL pack_arr ( jpoce,  rainrm_dta(1:jpoce,jscal), trc_data(1:jpi,1:jpj,15), iarroce(1:jpoce) ) 
    166170      rainrm_dta(1:jpoce,jscal) = rainrm_dta(1:jpoce,jscal) * 1e-4 
    167       ! vector temperature [�C] and salinity  
    168       CALL pack_arr ( jpoce,  temp(1:jpoce), trc_data(1:jpi,1:jpj,15), iarroce(1:jpoce) ) 
    169       CALL pack_arr ( jpoce,  salt(1:jpoce), trc_data(1:jpi,1:jpj,16), iarroce(1:jpoce) ) 
     171 
     172      ! vector temperature [°C] and salinity  
     173      CALL pack_arr ( jpoce,  temp(1:jpoce), trc_data(1:jpi,1:jpj,16), iarroce(1:jpoce) ) 
     174      CALL pack_arr ( jpoce,  salt(1:jpoce), trc_data(1:jpi,1:jpj,17), iarroce(1:jpoce) ) 
    170175       
    171176      ! Clay rain rate in [mol/(cm**2.s)]  
     
    174179      CALL pack_arr ( jpoce,  rainrm_dta(1:jpoce,jsclay), dust(1:jpi,1:jpj), iarroce(1:jpoce) ) 
    175180      rainrm_dta(1:jpoce,jsclay) = rainrm_dta(1:jpoce,jsclay) * conv2 / mol_wgt(jsclay)   & 
    176       &                            + wacc(1:jpoce) * por1(2) * denssol / mol_wgt(jsclay) / ( rsecday * 365.0 ) 
    177       rainrm_dta(1:jpoce,jsclay) = rainrm_dta(1:jpoce,jsclay) * 0.965 
    178       rainrm_dta(1:jpoce,jsfeo)  = rainrm_dta(1:jpoce,jsclay) * mol_wgt(jsclay) / mol_wgt(jsfeo) * 0.035 / 0.965 
     181      &                            + wacc(1:jpoce) * por1(2) * dens_sol(jsclay) / mol_wgt(jsclay) / ( rday * 365.0 ) 
     182      rainrm_dta(1:jpoce,jsfeo)  = rainrm_dta(1:jpoce,jsclay) * mol_wgt(jsclay) / mol_wgt(jsfeo) * 0.035 * 0.5 
     183      rainrm_dta(1:jpoce,jsclay) = rainrm_dta(1:jpoce,jsclay) * ( 1.0 - 0.035 * 0.5 )  
     184      CALL unpack_arr ( jpoce, zddust(1:jpi,1:jpj), iarroce(1:jpoce), wacc(1:jpoce) ) 
     185      zddust(:,:) = dust(:,:) + zddust(:,:) / ( rday * 365.0 ) * por1(2) * dens_sol(jsclay) / conv2 
     186 
    179187!    rainrm_dta(1:jpoce,jsclay) = 1.0E-4 * conv2 / mol_wgt(jsclay) 
    180188 
     
    183191 
    184192      ! Fe/C ratio in sinking particles that fall to the sediments 
    185       CALL pack_arr ( jpoce,  fecratio(1:jpoce), trc_data(1:jpi,1:jpj,17), iarroce(1:jpoce) ) 
    186  
    187       sedligand(:,1) = 1.E-9 
     193      CALL pack_arr ( jpoce,  fecratio(1:jpoce), trc_data(1:jpi,1:jpj,18), iarroce(1:jpoce) ) 
    188194 
    189195      ! sediment pore water at 1st layer (k=1) 
    190       DO jw = 1, jpwat 
    191          pwcp(1:jpoce,1,jw) = pwcp_dta(1:jpoce,jw) 
    192       ENDDO 
    193  
    194       !  rain 
    195       DO js = 1, jpsol 
    196          rainrm(1:jpoce,js) = rainrm_dta(1:jpoce,js) 
    197       ENDDO 
     196      pwcp(1:jpoce,1,1:jpwat) = pwcp_dta(1:jpoce,1:jpwat) 
    198197 
    199198      ! Calculation of raintg of each sol. comp.: rainrm in [g/(cm**2.s)] 
    200199      DO js = 1, jpsol 
    201          rainrg(1:jpoce,js) = rainrm(1:jpoce,js) * mol_wgt(js) 
     200         rainrg(1:jpoce,js) = rainrm_dta(1:jpoce,js) * mol_wgt(js) 
    202201      ENDDO 
    203202 
    204       ! Calculation of raintg = total massic flux rained in each cell (sum of sol. comp.) 
    205       raintg(:) = 0. 
     203      ! computation of dzdep = total thickness of solid material rained [cm] in each cell 
     204      dzdep(:) = 0. 
    206205      DO js = 1, jpsol 
    207          raintg(1:jpoce) = raintg(1:jpoce) + rainrg(1:jpoce,js) 
    208       ENDDO 
    209  
    210       ! computation of dzdep = total thickness of solid material rained [cm] in each cell 
    211       dzdep(1:jpoce) = raintg(1:jpoce) * rdtsed(2)  
     206         dzdep(1:jpoce) = dzdep(1:jpoce) + rainrg(1:jpoce,js) * dtsed / ( dens_sol(js) * por1(2) ) 
     207      END DO 
    212208 
    213209      IF( lk_iomput ) THEN 
    214           IF( iom_use("sflxclay" ) ) CALL iom_put( "sflxclay", dust(:,:) * conv2 * 1E4 ) 
    215           IF( iom_use("sflxcal" ) )  CALL iom_put( "sflxcal", trc_data(:,:,13) ) 
    216           IF( iom_use("sflxbsi" ) )  CALL iom_put( "sflxbsi", trc_data(:,:,10) ) 
    217           IF( iom_use("sflxpoc" ) )  CALL iom_put( "sflxpoc", trc_data(:,:,11) + trc_data(:,:,12) ) 
     210          IF( iom_use("sflxclay" ) ) CALL iom_put( "sflxclay", zddust(:,:) * 1E3 / 1.E4 ) 
     211          IF( iom_use("sflxcal" ) )  CALL iom_put( "sflxcal", trc_data(:,:,15) / 1.E4 ) 
     212          IF( iom_use("sflxbsi" ) )  CALL iom_put( "sflxbsi", trc_data(:,:,12) / 1.E4 ) 
     213          IF( iom_use("sflxpoc" ) )  CALL iom_put( "sflxpoc", ( trc_data(:,:,13) + trc_data(:,:,14) ) / 1.E4 ) 
    218214      ENDIF 
    219215 
Note: See TracChangeset for help on using the changeset viewer.