subroutine tranb21(utot ,d50 ,d90 ,h ,par , & & sbot ,ssus) !----- GPL --------------------------------------------------------------------- ! ! Copyright (C) Stichting Deltares, 2011-2017. ! ! This program is free software: you can redistribute it and/or modify ! it under the terms of the GNU General Public License as published by ! the Free Software Foundation version 3. ! ! This program is distributed in the hope that it will be useful, ! but WITHOUT ANY WARRANTY; without even the implied warranty of ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ! GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License ! along with this program. If not, see . ! ! contact: delft3d.support@deltares.nl ! Stichting Deltares ! P.O. Box 177 ! 2600 MH Delft, The Netherlands ! ! All indications and logos of, and references to, "Delft3D" and "Deltares" ! are registered trademarks of Stichting Deltares, and remain the property of ! Stichting Deltares. All rights reserved. ! !------------------------------------------------------------------------------- ! $Id: tranb7.f90 5717 2016-01-12 11:35:24Z mourits $ ! $HeadURL: https://svn.oss.deltares.nl/repos/delft3d/tags/6686/src/utils_gpl/morphology/packages/morphology_kernel/src/tranb7.f90 $ !!--description----------------------------------------------------------------- ! ! computes sediment transport according to ! Nino & Garcia (1998) ! !!--pseudo code and references-------------------------------------------------- ! NONE !!--declarations---------------------------------------------------------------- use precision implicit none ! ! Call variables ! real(fp) , intent(in) :: d50 ! grain size diameter (first specified diameter) real(fp) , intent(in) :: d90 ! grain size diameter (first specified diameter) real(fp) , intent(in) :: h ! water depth real(fp) , intent(out) :: sbot ! bed load transport real(fp) , intent(out) :: ssus ! suspended sediment transport real(fp) , intent(in) :: utot ! flow velocity real(fp), dimension(30), intent(in) :: par ! sediment parameter list ! ! Local variables ! real(fp) :: a real(fp) :: ah real(fp) :: alf1 real(fp) :: beta ! lowest level of integration interval over vertical real(fp) :: ca real(fp) :: del real(fp) :: dstar real(fp) :: fc real(fp) :: ff ! coriolis coefficient real(fp) :: ag ! gravity acceleration real(fp) :: psi real(fp) :: rhosol ! density of sediment real(fp) :: rhowat ! density of water real(fp) :: rksc real(fp) :: rmuc real(fp) :: rnu ! laminar viscosity of water real(fp) :: t ! dimensionless relative shear stress real(fp) :: tbc real(fp) :: tbce real(fp) :: tbcr real(fp) :: thetcr real(fp) :: ustar real(fp) :: ws ! settling velocity real(fp) :: zc real(fp) :: mud_d ! dynamic friction coefficient, default = 0.23. real(fp), external :: shld ! !! executable statements ------------------------------------------------------- ! sbot = 0.0_fp ssus = 0.0_fp ! ag = par(1) rhowat = par(2) rhosol = par(3) del = par(4) rnu = par(5) ! rksc = par(11) mud_d = par(12) ! if (h/rksc<1.33_fp .or. utot<1.e-3_fp) then return endif ! a = rksc dstar = d50*(del*ag/rnu/rnu)**(1.0_fp/3.0_fp) ! rmuc = ( log10(12.0_fp*h/rksc) / log10(12.0_fp*h/3.0_fp/d90) )**2 fc = 0.24_fp * (log10(12.0_fp*h/rksc))**( - 2) tbc = 0.125_fp * rhowat * fc * utot**2 tbce = rmuc * tbc thetcr = shld(dstar) tbcr = (rhosol-rhowat) * ag * d50 * thetcr sbot = sqrt(ag*del*d50) * d50 * (12.0_fp/max(mud_d, 0.0_fp)) * (tbce-tbcr) * (tbce**(0.5_fp)-0.7_fp*tbcr**0.5_fp) / rhosol ! [m2/s] end subroutine tranb21