management_distribribute Subroutine

public subroutine management_distribribute(pS, withdrawal_act, daycounter, ida, iyr)

If there is enough water to satisfy total demand of all users in subbasin


TSub (current subbasin)

add actual withdrawals of all water users from source subbasin


TWU (current water user)

calculate volume delivered to water user


Irrigation

account for irrigation water users !! pWU%supplied should not be added to %inflow, because the irrigation supply is added in hydrotope !! %inflow is added to sda or varoute in "subbasin" and/or "add"

--------------------------------------------------------------

        *****

If there is NOT enough water to satisfy total demand of all users in subbasin *



TSub (current subbasin)


TWU (current water user)

add actual withdrawals of all water users from source subbasin


Irrigation

account for irrigation water users !! pWU%supplied should not be added to %inflow, because the irrigation supply is added in hydrotope !! %inflow is added to sda or varoute in "subbasin" and/or "add"


Arguments

Type IntentOptional AttributesName
type(TSubbasin), POINTER:: pS
real(kind=dp), intent(in) :: withdrawal_act
integer, intent(in) :: daycounter
integer, intent(in) :: ida
integer, intent(in) :: iyr

Calls

proc~~management_distribribute~~CallsGraph proc~management_distribribute management_distribribute proc~management_user_pointer management_user_pointer proc~management_distribribute->proc~management_user_pointer proc~management_subbasin_pointer management_subbasin_pointer proc~management_distribribute->proc~management_subbasin_pointer proc~management_is_active_period management_is_active_period proc~management_distribribute->proc~management_is_active_period proc~log_error log_error proc~management_user_pointer->proc~log_error proc~log_message log_message proc~log_error->proc~log_message proc~log_write log_write proc~log_message->proc~log_write proc~log_format_message log_format_message proc~log_message->proc~log_format_message proc~to_string to_string proc~log_write->proc~to_string proc~date_time_str date_time_str proc~log_format_message->proc~date_time_str proc~colourise colourise proc~log_format_message->proc~colourise proc~string_index string_index proc~colourise->proc~string_index

Contents


Source Code

  subroutine management_distribribute(ps, withdrawal_act, daycounter, ida, iyr)
    integer, intent(in) :: daycounter
    integer, intent(in) :: ida
    integer, intent(in) :: iyr
    ! called from RESERVOIR module
    ! pointer on actual subbasin
    TYPE (TSubbasin), POINTER :: pS
    ! [m3] amount of water withdrawn from reservoir
    real(dp), intent(in) :: withdrawal_act
    ! pointer on destination subbasin (TSub)
    TYPE (TSubbasin), POINTER :: pSd
    ! pointer on actual wtaer user (TWU)
    TYPE (TWaterUser), POINTER :: pWU
    integer :: i, day

    day = daycounter

    !-------------------------------------------------------
    ! If there is enough water to satisfy total demand of all users in subbasin
    !-------------------------------------------------------
    if (withdrawal_act >= pS % totDemand(day) * 86400.) then
      ! allocate water to corresponding water user(s)
      do i = 1, pS % nWU ! loop over water user(s) in actual subbasin
        pWU => management_user_pointer(pS % pos(i)) ! pointer on current water user
        ! transfer to another subbasin .OR. to external destination .OR. to irrigation user
        if (pWU % wu_opt <= 2 .AND. management_is_active_period(iyr, ida, pWU) ) then
          if (pWU % subs == pS % subnr) then ! if the current subbasin is a water source
            !-----------------------------------------------------------------
            ! TSub (current subbasin)
            !-----------------------------------------------------------------
            ! add actual withdrawals of all water users from source subbasin
            pS % withdrawal(day) = pS % withdrawal(day) + pWU % data(day) ! deliver what is demanded

            ! add actual losses of all water users from source subbasin
            pS % tr_losses_out(day) = pS % tr_losses_out(day) + pWU % data(day) * (1. - pWU % tr_eff) ! knowing that demand can be delivered

            ! add withdrawal day as %inflow and %tr_losses_in to destination subbasin
            if (pWU % wu_opt == 1) then
              pSd => management_subbasin_pointer(pWU % subd)
              pSd % inflow(day) = pSd % inflow(day) + pWU % data(day) * pWU % tr_eff
              pSd % tr_losses_in(day) = pSd % tr_losses_in(day) + pWU % data(day) * (1. - pWU % tr_eff)
            end if
            !-----------------------------------------------------------------

            !-----------------------------------------------------------------
            ! TWU (current water user)
            !-----------------------------------------------------------------
            ! calculate volume delivered to water user
            pWU % supplied(day) = pWU % data(day) * pWU % tr_eff ! [m3 / s]

            ! calculate losses during transfer
            pWU % tr_losses(day) = pWU % data(day) * (1. - pWU % tr_eff) ! [m3 / s]
            !-----------------------------------------------------------------
          end if
        end if ! ( pWU % wu_opt <= 2 )

        !-----------------------------------------------------------------
        ! Irrigation
        !-----------------------------------------------------------------
        ! account for irrigation water users
        if (day > 1) then
          if (pWU % wu_opt == 4 .AND. management_is_active_period(iyr, ida, pWU) ) then
            ! calculate volume delivered to water user
            ! add actual withdrawals from irrigation WU
            ! pS%irrDemand is corrected by irrigation practices and efficiencies
            pS % withdrawal(day) = pS % withdrawal(day) + pWU % irrigationDemand(day - 1) ! deliver what is demanded
            ! add actual losses of irrigation water user
            pS % tr_losses_out(day) = pS % tr_losses_out(day) + pWU % irrigationDemand(day - 1) * (1. - pWU % tr_eff) ! knowing that demand can be delivered

            pWU % supplied(day) = pWU % irrigationDemand(day - 1) * pWU % tr_eff ! [m3 / s]
            wam_supplied_summary(day) = wam_supplied_summary(day) + pWU % supplied(day)

            pWU % tr_losses(day) = pWU % irrigationDemand(day - 1) * (1. - pWU % tr_eff) ! [m3 / s]

            if (pWU % subs /= pWU % subd) then
              pSd => management_subbasin_pointer(pWU % subd)
              !!!! pWU%supplied should not be added to %inflow, because the irrigation supply is added in hydrotope
              !!!! %inflow is added to sda or varoute in "subbasin" and/or "add"
              !pSd%inflow(day) = pSd%inflow(day) + pWU%supplied(day) ! [m3/s]
              pSd % tr_losses_in(day) = pSd % tr_losses_in(day) + pWU % tr_losses(day)
            end if
          end if
        end if
        !-----------------------------------------------------------------
      end do ! i = 1, pS % nWU
    end if

    !-------------------------------------------------------
    !            *****
    ! If there is NOT enough water to satisfy total demand of all users in subbasin
    !            *****
    !-------------------------------------------------------
    if (withdrawal_act < pS % totDemand(day) * 86400. ) then ! in [m3]
      ! The amount of available water might be shared by several competing water users.
      ! In this version, all water users are treated according to their demand, meaning that
      ! water user with highest demand gets highest share.
      ! Another option to distribute the available volume is for instance:
      !  - by water user priorities (highest gets all, second and third only what remains from higher priority users)
      do i = 1, pS % nWU ! loop over water user(s) in actual subbasin
        pWU => management_user_pointer(pS % pos(i)) ! pointer on current water user
        if (pWU%wu_opt <= 2 .AND. management_is_active_period(iyr, ida, pWU) ) then ! if water user is of type 'output'
          if (pWU % subs == pS % subnr) then ! if the current subbasin is a water source
            !-----------------------------------------------------------------
            ! TSub (current subbasin)
            !-----------------------------------------------------------------
            pS % withdrawal(day) = real( &
              pS % withdrawal(day) + &
              pWU % data(day) / pS % totDemand(day) * &
              withdrawal_act / 86400.) ! * pWU % tr_eff ! [m3 / s]

            ! calculate losses during transfer
            pS % tr_losses_out(day) = real( &
              pS % tr_losses_out(day) + &
              pWU % data(day) / pS % totDemand(day) * &
              withdrawal_act / 86400. * (1. - pWU % tr_eff)) ! [m3 / s]

            ! add withdrawal as %inflow and %tr_losses_in to destination subbasin
            if (pWU % wu_opt == 1) then
              pSd => management_subbasin_pointer(pWU % subd)
              pSd % inflow(day) = real( &
                pSd % inflow(day) + &
                pWU % data(day) / pS % totDemand(day) * &
                withdrawal_act / 86400. * pWU % tr_eff)
              pSd % tr_losses_in(day) = real( &
                pSd % tr_losses_in(day) + &
                pWU % data(day) / pS % totDemand(day) * &
                withdrawal_act / 86400. * (1. - pWU % tr_eff))
            end if

            !-----------------------------------------------------------------
            ! TWU (current water user)
            !-----------------------------------------------------------------
            ! add actual withdrawals of all water users from source subbasin
            pWU % supplied(day) = real( &
              pWU % data(day) / pS % totDemand(day) * &
              withdrawal_act / 86400. * pWU % tr_eff) ! [m3 / s]

            ! calculate losses during transfer
            pWU % tr_losses(day) = real( &
              pWU % data(day) / pS % totDemand(day) * &
              withdrawal_act / 86400. * (1. - pWU % tr_eff)) ! [m3 / s]
            !-----------------------------------------------------------------
          end if
        end if ! ( pWU % wu_opt <= 2 )

        !-----------------------------------------------------------------
        ! Irrigation
        !-----------------------------------------------------------------
        ! account for irrigation water users
        if (day > 1) then
          if (pWU % wu_opt == 4 .AND. management_is_active_period(iyr, ida, pWU) ) then
            ! add actual withdrawals from irrigation WU
            ! pS%irrDemand is corrected by irrigation practices and efficiencies
            pS % withdrawal(day) = real( &
              pS % withdrawal(day) + &
              pWU % irrigationDemand(day - 1) / pS % totDemand(day) * &
              withdrawal_act / 86400.)

            ! add actual losses of irrigation water user, knowing that demand can be delivered
            pS % tr_losses_out(day) = real( &
              pS % tr_losses_out(day) + &
              pWU % irrigationDemand(day - 1) / &
              pS % totDemand(day) * withdrawal_act / 86400. * (1. - pWU % tr_eff))

            ! calculate volume delivered to water user
            pWU % supplied(day) = real( &
              pWU % irrigationDemand(day - 1) / pS % totDemand(day) * &
              withdrawal_act / 86400. * pWU % tr_eff) ! [m3 / s]

            wam_supplied_summary(day) = wam_supplied_summary(day) + pWU % supplied(day)

            pWU % tr_losses(day) = real( &
              pWU % irrigationDemand(day - 1) / pS % totDemand(day) * &
              withdrawal_act / 86400. * (1. - pWU % tr_eff)) ! [m3 / s]

            if (pWU % subs /= pWU % subd) then
              pSd => management_subbasin_pointer(pWU % subd)
              !!!! pWU%supplied should not be added to %inflow, because the irrigation supply is added in hydrotope
              !!!! %inflow is added to sda or varoute in "subbasin" and/or "add"
              !pSd%inflow(day) = pSd%inflow(day) + pWU%supplied(day) ! pWU%irrigationDemand(day)/pS%totDemand(day) * withdrawal_act/86400. * pWU%tr_eff ! [m3/s]
              pSd % tr_losses_in(day) = pSd % tr_losses_in(day) + pWU % tr_losses(day) ! pWU % irrigationDemand(day) / pS % totDemand(day) * withdrawal_act / 86400. * (1. - pWU % tr_eff)
            end if
          end if
        end if
        !-----------------------------------------------------------------

      end do ! i = 1, pS % nWU
    end if ! ( withdrawal_act < pS % totDemand(day) * 86400. )
  end subroutine management_distribribute