erosion_cklsp_factor Subroutine

public subroutine erosion_cklsp_factor(j, je, k, cva, ek, igro, nucr, is_cropland, is_natural_vegetation, is_forest)

Arguments

Type IntentOptional AttributesName
integer :: j
integer :: je
integer :: k
real(kind=dp), intent(in), dimension(:, :):: cva
real(kind=dp), intent(in), dimension(:):: ek
integer, intent(in), dimension(:, :):: igro
integer, intent(in), dimension(:, :):: nucr
logical, intent(in) :: is_cropland
logical, intent(in) :: is_natural_vegetation
logical, intent(in) :: is_forest

Called by

proc~~erosion_cklsp_factor~~CalledByGraph proc~erosion_cklsp_factor erosion_cklsp_factor proc~hydrotope_process hydrotope_process proc~hydrotope_process->proc~erosion_cklsp_factor proc~runsubbasin runsubbasin proc~runsubbasin->proc~hydrotope_process proc~time_process_day time_process_day proc~time_process_day->proc~runsubbasin proc~time_process_month time_process_month proc~time_process_month->proc~time_process_day proc~time_process_years time_process_years proc~time_process_years->proc~time_process_month program~swim swim program~swim->proc~time_process_years

Contents

Source Code


Source Code

  subroutine erosion_cklsp_factor(j, je, k, cva, ek, igro, nucr, is_cropland, is_natural_vegetation, is_forest)
    !**** PURPOSE: THIS SUBROUTINE ESTIMATES COMBINED CKLSP factor
    !     FOR WATER EROSION
    !**** CALLED IN: HYDROTOP
    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    !     PARAMETERS & VARIABLES
    !
    !      >>>>> COMMON PARAMETERS & VARIABLES
    !      cklsp(j, je) = combined c, k, ls, p factor
    !      cva(j, je) = land cover, kg/ha, calc in crpmd
    !      cvm(icr) = minimum value of C factor for water erosion, readcrp
    !      dm(j, je) = total biomass, kg/ha
    !      ecp(j) = P factor, readsub
    !      ek(k) = USLE soil K factor, read in readsol
    !      ida = current day
    !      ieros = switch code to print from eros()
    !      iersb = number of subbasin to print from eros(), if ieros = 1
    !      igro(j, je) = vegetation index for cropland, = 1 if planted
    !      nucr(j, je) = crop number
    !      sl(j) = USLE slope length/slope steepness factor
    !      >>>>>

    !      >>>>> STATIC PARAMETER
    !      c = C (land cover) factor
    !      >>>>>
    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

    real(dp), dimension(:, :), intent(in) :: cva
    real(dp), dimension(:), intent(in) :: ek
    integer, dimension(:, :), intent(in) :: igro
    integer, dimension(:, :), intent(in) :: nucr
    logical, intent(in) :: is_cropland, is_natural_vegetation, is_forest
    integer j, je, k
    real(dp) c

    c = 0.
    if (is_natural_vegetation) c = 0.1
    if (is_forest) c = 0.45
    if (is_cropland) then
      if (igro(j, je) .eq. 1) then
        c = exp((- .2231 - cvm(nucr(j, je))) * &
            exp(- .00115 * cva(j, je)) + cvm(nucr(j, je)))
      else
        c = 0.8
      endif
    endif

    !**** CALC combined c, k, ls, p factor
    cklsp(j, je) = c * ek(k) * ecp(j) * sl(j)

    return
  end subroutine erosion_cklsp_factor