management_transfer_out Subroutine

public subroutine management_transfer_out(sub, surfaceR, subsurfaceR, day, ida, iyr)

check if flow values are negative


calculate available volume at subbains' outlet


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

!! 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"


! NOTE: the values of varoute(2, ihout) and varaoute(8, ihout) are modified here !!!


        *****

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"


! NOTE: the values of varoute(2, ihout) and varaoute(8, ihout) are modified here !!!

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: sub
real(kind=dp), intent(inout) :: surfaceR
real(kind=dp), intent(inout) :: subsurfaceR
integer, intent(in) :: day
integer, intent(in) :: ida
integer, intent(in) :: iyr

Calls

proc~~management_transfer_out~~CallsGraph proc~management_transfer_out management_transfer_out proc~log_warn log_warn proc~management_transfer_out->proc~log_warn proc~management_user_pointer management_user_pointer proc~management_transfer_out->proc~management_user_pointer proc~management_subbasin_pointer management_subbasin_pointer proc~management_transfer_out->proc~management_subbasin_pointer proc~management_is_active_period management_is_active_period proc~management_transfer_out->proc~management_is_active_period proc~log_message log_message proc~log_warn->proc~log_message proc~log_error log_error proc~management_user_pointer->proc~log_error 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~log_error->proc~log_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

Called by

proc~~management_transfer_out~~CalledByGraph proc~management_transfer_out management_transfer_out proc~river_route_add river_route_add proc~river_route_add->proc~management_transfer_out proc~runsubbasin runsubbasin proc~runsubbasin->proc~management_transfer_out proc~time_process_day time_process_day proc~time_process_day->proc~river_route_add 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

  subroutine management_transfer_out(sub, surfacer, subsurfacer, day, ida, iyr)
    integer, intent(in) :: ida
    integer, intent(in) :: iyr
    ! integer, dimension(:), intent(in) :: subs
    ! This subroutine is called from subroutine 'subbasin' (if subbasin is a headwater)
    ! OR from subroutine 'add' if it is a subbasin where the water is routed through
    ! It calculates withdrawals, supply, and transmission losses.
    ! subbasin number
    integer, intent(in) :: sub
    ! sda(2, sub), sda(8, sub)
    real(dp), intent(inout) :: surfaceR, subsurfaceR
    ! current day of simulation, not julian day
    integer, intent(in) :: day
    integer :: i
    ! [m3] subbasins' inflow + own contributions
    real(dp) :: voltot
    ! [m3] volume of water available for downstream routing
    real(dp) :: available_vol
    ! fraction of surface runoff contribution to gw contribution
    real(dp) :: frac_sr
    ! pointer on actual TSub
    TYPE (TSubbasin), POINTER :: pS
    ! pointer on destination TSub
    TYPE (TSubbasin), POINTER :: pSd
    ! pointer on actual TWU
    TYPE (TWaterUser), POINTER :: pWU

    available_vol = 0.
    pS => management_subbasin_pointer(sub) ! pointer on actual subbasin

    if (pS % nWUout > 0) then ! do water users exist receiving water from this subbasin

      !-------------------------------------------------------
      ! check if flow values are negative
      !-------------------------------------------------------
      if (surfaceR < 0.) then
        call log_warn("wam", "Surface runoff (varoute2, x) is negative! Subbasin:", int=sub)
        surfaceR = 1.e-6
      end if
      if (subsurfaceR < 0.) then
        call log_warn("wam", "Subsurface runoff (varoute8, x) is negative! Subbasin:", int=sub)
        subsurfaceR = 1.e-6
      end if

      !-------------------------------------------------------
      ! calculate available volume at subbains' outlet
      !-------------------------------------------------------
      voltot = max(0.0_dp, surfaceR) + max(0.0_dp, subsurfaceR) ! [m3]
      ! correct on minimal flows required in subbasin
      available_vol = voltot - pS % Q_min(day) * 86400. ! [m3]

      if (available_vol > 0. .AND. pS % totDemand(day) > 0. ) then
        frac_sr = max(0.0_dp, surfaceR) / voltot

        !-------------------------------------------------------
        ! If there is enough water to satisfy total demand of all users in subbasin
        !-------------------------------------------------------
        if (available_vol >= pS % totDemand(day) * 86400. ) then ! in [m3]
          ! 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 ! ( pWU % wu_opt <= 2 .OR. pWU % wu_opt == 4 )
            end if ! pWU % wu_opt <= 2


            !-----------------------------------------------------------------
            ! Irrigation
            !-----------------------------------------------------------------
            if (day > 1) then
              ! account for irrigation water users
              if (pWU % wu_opt == 4 .AND. pWU % subs > 0 .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
                if (pWU % irr_opt == 1) &
                  ! deliver what is demanded according to input time series
                  pS % withdrawal(day) = pS % withdrawal(day) + pWU % data(day - 1)
                if (pWU % irr_opt == 2) &
                  ! deliver what is demanded according to calculated plant demand
                  pS % withdrawal(day) = pS % withdrawal(day) + pWU % irrigationDemand(day - 1)

                ! 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

                if (pWU % irr_opt == 1) pWU % supplied(day) = pWU % data(day) * pWU % tr_eff ! [m3 / s]
                if (pWU % irr_opt == 2) 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]
                pWU % tr_losses(day) = pWU % supplied(day) * (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) * pWU%tr_eff ! [m3/s]
                  pSd % tr_losses_in(day) = pSd % tr_losses_in(day) + pWU % tr_losses(day) !  pWU % irrigationDemand(day) * (1. - pWU % tr_eff)
                end if
              end if !( pWU % wu_opt == 4 .AND. pWU % subs > 0 .AND. pS % irrDemand(day) > 0. )
            end if
            !-----------------------------------------------------------------
          end do ! i = 1, pS % nWU

          ! withdraw total demand from surface and subsurface runoff
          !!! NOTE: the values of varoute(2, ihout) and varaoute(8, ihout) are modified here !!!
          surfaceR = surfaceR - (pS % totDemand(day) * 86400. * frac_sr) ! [m3]
          subsurfaceR = subsurfaceR - (pS % totDemand(day) * 86400. * (1. - frac_sr)) ! [m3]
        end if ! ( available_vol >= pS % totDemand(day))
        !-------------------------------------------------------

        !-------------------------------------------------------
        !            *****
        ! If there is NOT enough water to satisfy total demand of all users in subbasin
        !            *****
        !-------------------------------------------------------
        if (available_vol < 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)

          frac_sr = max(0.0_dp, surfaceR) / (max(0.0_dp, surfaceR) + max(0.0_dp, subsurfaceR))

          do i = 1, pS % nWU ! loop over water user(s) in actual subbasin
            pWU => TWU(pS % pos(i)) ! pointer to 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) * &
                  available_vol / 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) * &
                  available_vol / 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) * &
                    available_vol / 86400. * pWU % tr_eff)
                  pSd % tr_losses_in(day) = real( &
                    pSd % tr_losses_in(day) + &
                    pWU % data(day) / pS % totDemand(day) * &
                    available_vol / 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) * &
                  available_vol / 86400. * pWU % tr_eff) ! [m3 / s]

                ! calculate losses during transfer
                pWU % tr_losses(day) = real( &
                  pWU % data(day) / pS % totDemand(day) * &
                  available_vol / 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. pWU % subs > 0 .AND. management_is_active_period(iyr, ida, pWU) ) then
                ! add actual withdrawals from irrigation WU
                ! pS%irrDemand is corrected by irrigation practices and efficiencies

                ! demand/supply from input time series
                if (pWU % irr_opt == 1) &
                  pS % withdrawal(day) = real( &
                    pS % withdrawal(day) + &
                    pWU % data(day - 1) / pS % totDemand(day) * &
                    available_vol / 86400.)
                ! demand/supply from plant demand
                if (pWU % irr_opt == 2) &
                  pS % withdrawal(day) = real(pS % withdrawal(day) + pWU % irrigationDemand(day - 1) / pS % totDemand(day) &
                                                          * available_vol / 86400.)

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

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

                pWU % tr_losses(day) = pWU % supplied(day) * (1. - pWU % tr_eff) ! pS % irrDemand(day) / pS % totDemand(day) * available_vol / 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-1)/pS%totDemand(day) * available_vol/86400. * pWU%tr_eff ! [m3/s]
                  pSd % tr_losses_in(day) = pSd % tr_losses_in(day) + pWU % tr_losses(day) ! pWU % irrigationDemand(day - 1) / pS % totDemand(day) * available_vol / 86400. * (1. - pWU % tr_eff)
                end if
              end if
            end if
            !-----------------------------------------------------------------
          end do ! i = 1, pS % nWU

          ! withdraw total demand from surface and subsurface runoff
          !!! NOTE: the values of varoute(2, ihout) and varaoute(8, ihout) are modified here !!!
          surfaceR = surfaceR - (available_vol * frac_sr) ! [m3]
          subsurfaceR = subsurfaceR - (available_vol * (1. - frac_sr)) ! [m3]

        end if ! ( available_vol < pS % totDemand(day) * 86400. )
        !-------------------------------------------------------

      else
        ! The available volume at subbasin outlet minus minimal flows is negative.
        ! Hence, there is nothing to do here because all variables affected, such as
        ! pWU%delivered, pS%tr_losses, pS%supply were initialised with 0. for every day.

      end if ! if (available_vol > 0. .AND. pS % totDemand(day) > 0. )

    else ! no output water user in this subbasin
    end if

  end subroutine management_transfer_out