river_route_add Subroutine

public subroutine river_route_add(bRunoffdat, ihout, inum1, inum2, additionalGwUptake, bWAM_Module, daycounter, ida, iyr, mb, nqobs, obssb, obs_discharge, runs, subouthyd, inum1s, bRsvModule, rsv_is_operational, rsvSubbasin)

Uses

  • proc~~river_route_add~~UsesGraph proc~river_route_add river_route_add module~output output proc~river_route_add->module~output module~management management proc~river_route_add->module~management module~utilities utilities module~output->module~utilities module~management->module~utilities

! DO NOT CALL add_varoute !!!

Withdraw water from subbasin outlet but only if subbasin is not a headwater .and. not a reservoir.


ATTENTION: The values of varoute(2, j) and varoute(8, j) may be changed!

! DO NOT CALL add_varoute AGAIN !!!

Withdraw water from subbasin outlet but only if subbasin is not a headwater .and. not a reservoir.


ATTENTION: The values of varoute(2, j) and varoute(8, j) may be changed!

! DO NOT CALL add_varoute AGAIN !!!


Arguments

Type IntentOptional AttributesName
logical, intent(in) :: bRunoffdat
integer, intent(in) :: ihout
integer, intent(in) :: inum1
integer, intent(in) :: inum2
real(kind=dp), intent(out), dimension(:):: additionalGwUptake
logical, intent(in) :: bWAM_Module
integer, intent(in) :: daycounter
integer, intent(in) :: ida
integer, intent(in) :: iyr
integer, intent(in) :: mb
integer, intent(in) :: nqobs
integer, intent(in), dimension(100):: obssb
real(kind=dp), intent(in), dimension(:, :):: obs_discharge
real(kind=dp), intent(inout), dimension(366):: runs
integer, intent(in), dimension(:):: subouthyd
integer, intent(in), dimension(:):: inum1s
logical, intent(in) :: bRsvModule
logical, intent(in) :: rsv_is_operational
integer, intent(in), dimension(:):: rsvSubbasin

Calls

proc~~river_route_add~~CallsGraph proc~river_route_add river_route_add proc~management_transfer_out management_transfer_out proc~river_route_add->proc~management_transfer_out proc~management_is_transfer_subbasin management_is_transfer_subbasin proc~river_route_add->proc~management_is_transfer_subbasin proc~output_store_subbasin_values output_store_subbasin_values proc~river_route_add->proc~output_store_subbasin_values proc~management_subbasin_pointer management_subbasin_pointer proc~river_route_add->proc~management_subbasin_pointer proc~management_transfer_out->proc~management_subbasin_pointer 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_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~~river_route_add~~CalledByGraph proc~river_route_add river_route_add proc~time_process_day time_process_day proc~time_process_day->proc~river_route_add 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 river_route_add(bRunoffdat, ihout, inum1, inum2, additionalGwUptake, bWAM_Module, daycounter, ida, iyr, mb, nqobs, obssb, obs_discharge, runs, subouthyd, inum1s, bRsvModule, rsv_is_operational, rsvSubbasin)
    !**** PURPOSE: THIS SUBROUTINE ADDS OUTPUTS FOR ROUTING
    !**** CALLED IN: MAIN
    !     ATTN! Look at the final line in the .fig file to define
    !           where the output has to be written: in route() or in add()
    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    !     PARAMETERS & VARIABLES
    !
    !      >>>>> PARAMETERS IN TITLE
    !tit icode = code to switch between routing subroutines (here: 2)
    !tit ihout = hydrological storage location
    !tit inum1 = reach number
    !tit inum2 = inflow hydrograph(inum2 hydrograph is routed through inum1)
    !      >>>>>

    !      >>>>> COMMON PARAMETERS & VARIABLES
    !      accf(4) = accumulated org. N, m3/sec.
    !      accf(5) = accumulated org. P, t
    !      accf(6) = accumulated NO3-N, kg
    !      ida = current day
    !      iy = current year as counter (1, ..., nbyr)
    !      iyr = current year
    !      runs(ida) = runoff simulated for the basin, m3/sec.
    !      varoute(1:8, ih) = vector for routing:
    !      Name Units Definition
    !      varoute(2, ih) |(m^3) |surface flow
    !      varoute(3, ih) |(tons) |sediment
    !      varoute(4, ih) |(kg) |organic N
    !      varoute(5, ih) |(kg) |organic P
    !      varoute(6, ih) |(kg) |nitrate N
    !      varoute(7, ih) |(kg) |soluble P
    !      varoute(8, ih) |(m^3) |subsurface + g-w flow
    !      >>>>>

    !      >>>>> STATIC PARAMETERS
    !      cnit = NO3-N concentration, mg/l
    !      >>>>>
    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

    use management, only : &
        TSubbasin, bWAMHydrograph, management_is_transfer_subbasin, &
        management_subbasin_pointer, management_transfer_out, management_transfer_out
    use output, only : output_store_subbasin_values

    logical, intent(in) :: bRunoffdat
    real(dp), dimension(:), intent(out) :: additionalGwUptake
    logical, intent(in) :: bWAM_Module
    integer, intent(in) :: daycounter
    integer, intent(in) :: ida
    integer, intent(in) :: iyr
    integer, intent(in) :: mb
    integer, intent(in) :: nqobs
    integer, dimension(100), intent(in) :: obssb
    real(dp), dimension(:, :), intent(in) :: obs_discharge
    real(dp), dimension(366), intent(inout) :: runs
    integer, dimension(:), intent(in) :: subouthyd
    integer, intent(in) :: ihout, inum1, inum2
    integer, dimension(:), intent(in) :: inum1s
    logical, intent(in) :: bRsvModule, rsv_is_operational
    integer, dimension(:), intent(in) :: rsvSubbasin

    integer :: i
    real(dp) :: cnit
    ! ### RESERVOIR MODULE
    logical :: bAdd
    !#### WATER MANAGEMENT MODULE ####
    TYPE (TSubbasin), POINTER :: pS ! pointer on actual TSub

    if (ida .eq. 1 .and. inum2 .eq. 1) then
      accf(4) = 0.
      accf(5) = 0.
      accf(6) = 0.
    end if

    !#######################
    ! ### RESERVOIR MODULE
    !#######################
    bAdd = .true.

    if (bRsvModule) then
      if (inum2 <= mb) then
        if (rsvSubbasin(inum2) /= 0 .AND. rsv_is_operational) then
          varoute(2, ihout) = varoute(2, inum1)
          varoute(3, ihout) = varoute(3, inum1)
          varoute(4, ihout) = varoute(4, inum1)
          varoute(5, ihout) = varoute(5, inum1)
          varoute(6, ihout) = varoute(6, inum1)
          varoute(7, ihout) = varoute(7, inum1)
          varoute(8, ihout) = varoute(8, inum1)
          bAdd = .false. !!! DO NOT CALL add_varoute !!!
        else
          !#################################
          !#### WATER MANAGEMENT MODULE ####
          !#################################
          ! check if water management module is switched on
          if (bWAM_Module) then
            ! check if water transfers take place in current subbasin
            if (bWAMHydrograph(ihout) ) then
              if (management_is_transfer_subbasin(inum2) ) then
                pS => management_subbasin_pointer(inum2)
                call river_route_add_varoute
                !-------------------------------------------------------------
                ! Withdraw water from subbasin outlet
                ! but only if subbasin is not a headwater .and. not a reservoir.
                !-------------------------------------------------------------
                ! ATTENTION: The values of varoute(2, j) and varoute(8, j) may be changed!
                call management_transfer_out(inum2, varoute(2, ihout), varoute(8, ihout), daycounter, ida, iyr)

                pS % Q_act(daycounter) = real(varoute(2, ihout) / 86400. + varoute(8, ihout) / 86400.)
                !-------------------------------------------------------------
                bAdd = .false. !!! DO NOT CALL add_varoute AGAIN !!!
              end if ! ( wam_is_transfer_subbasin(inum2) )
            end if
          end if ! ( bWAM_Module )
          !#################################

        end if ! ( rsvSubbasin(inum2) /= 0 )
      end if ! if inum2 > mb

    else ! if (.NOT.bRsvModule)
      !#################################
      !#### WATER MANAGEMENT MODULE ####
      !#################################
      ! check if water management module is switched on
      if (bWAM_Module) then
        ! check if water transfers take place in current subbasin
        ! check if water transfers take place in current subbasin
        if (bWAMHydrograph(ihout) ) then
          if (management_is_transfer_subbasin(inum2) ) then
            pS => management_subbasin_pointer(inum2)
            call river_route_add_varoute
            !-------------------------------------------------------------
            ! Withdraw water from subbasin outlet
            ! but only if subbasin is not a headwater .and. not a reservoir.
            !-------------------------------------------------------------
            ! ATTENTION: The values of varoute(2, j) and varoute(8, j) may be changed!
            call management_transfer_out(inum2, varoute(2, ihout), varoute(8, ihout), daycounter, ida, iyr)

            pS % Q_act(daycounter) = real(varoute(2, ihout) / 86400. + varoute(8, ihout) / 86400.)
            !-------------------------------------------------------------
            bAdd = .false. !!! DO NOT CALL add_varoute AGAIN !!!
          end if ! ( wam_is_transfer_subbasin(inum2) )
        end if
      end if ! ( bWAM_Module )
      !#################################

    end if ! ( bRsvModule )
    !#######################! END IF ( bRsvModule )

    if (bAdd) call river_route_add_varoute !**** ADD FLOWS: 2 - surface flow, 8 - subsurface flow

    !*** Overwrite simulated routed discharge with observed, eg. for calibration
    if (bRunoffdat .and. nqobs > 1) then
      do i = 2, nqobs
        if (inum2 .eq. obssb(i) .and. obs_discharge(ida, i) >= 0. ) then
          varoute(2, ihout) = obs_discharge(ida, i) * 86400.
          varoute(8, ihout) = 0.
        endif
      enddo
    endif

    !**** WRITE DAILY OUTPUT in outlet (if inum2=1) to river output file unit=76
    !     WRITE is possible in variants - needed one should be opened
    if (inum2 == 1) then ! if inum2 is outlet (usually the last add command in the .fig file)

      if (bRsvModule) then ! if reservoir module is active
        if (rsvSubbasin(inum2) /= 0 ) then ! if subbasin inum2 is a reservoir
          runs(ida) = (varoute(2, inum1) + varoute(8, inum1)) / 86400.
        else
          runs(ida) = (varoute(2, ihout) + varoute(8, ihout)) / 86400.
        end if
      else
        runs(ida) = (varoute(2, ihout) + varoute(8, ihout)) / 86400.
      end if
      !runs(ida)=(varoute(2, ihout)+varoute(8, ihout))/86400.
      accf(4) = accf(4) + runs(ida)
      accf(5) = accf(5) + varoute(3, ihout)
      accf(6) = accf(6) + varoute(6, ihout)

      !**** CALC N CONCENTRATION
      !        varoute(6, ) - kg, runs - m3/sec, cnit - mg/l
      cnit = varoute(6, ihout) / runs(ida) / 86.4

      if (river_discharge_output_id > 0) then
        do i = 1, mb
          if (bRsvModule) then
            if (rsvSubbasin(i) /= 0 ) then ! if subbasin is a reservoir
              runsub_m3s(i) = (varoute(2, inum1s(subouthyd(i))) + varoute(8, inum1s(subouthyd(i)))) / 86400.
            else
              runsub_m3s(i) = (varoute(2, subouthyd(i)) + varoute(8, subouthyd(i))) / 86400.
            end if
          else
            runsub_m3s(i) = (varoute(2, subouthyd(i)) + varoute(8, subouthyd(i))) / 86400.
          end if
        end do

        call output_store_subbasin_values(river_discharge_output_id, runsub_m3s)
      end if

      additionalGwUptake(1:mb) = 0

    end if ! (inum2 .eq. 1)

  contains
    ! Subroutines inside the `add` subroutine

    !--------------------------------------------------------
    subroutine river_route_add_varoute
      varoute(2, ihout) = varoute(2, inum1) + varoute(2, inum2)
      varoute(3, ihout) = varoute(3, inum1) + varoute(3, inum2)
      varoute(4, ihout) = varoute(4, inum1) + varoute(4, inum2)
      varoute(5, ihout) = varoute(5, inum1) + varoute(5, inum2)
      varoute(6, ihout) = varoute(6, inum1) + varoute(6, inum2)
      varoute(7, ihout) = varoute(7, inum1) + varoute(7, inum2)
      varoute(8, ihout) = varoute(8, inum1) + varoute(8, inum2)
    end subroutine river_route_add_varoute
    !--------------------------------------------------------

  end subroutine river_route_add