Nodes of different colours represent the following:
Solid arrows point from a procedure to one which it calls. Dashed arrows point from an interface to procedures which implement that interface. This could include the module procedures in a generic interface or the implementation in a submodule of an interface in a parent module. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
SUBROUTINE setNativeVariables
! SUBROUTINE INFORMATION:
! AUTHOR Jason Glazer of GARD Analytics, Inc.
! DATE WRITTEN July 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Set up the "built in" i.e. native variables that hold
! the energy and demand from the simulation.
! METHODOLOGY EMPLOYED:
! REFERENCES:
! na
! USE STATEMENTS:
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: iTariff
INTEGER :: jPeriod
INTEGER :: kMonth
REAL(r64), DIMENSION(MaxNumMonths) :: monthVal
REAL(r64) :: bigNumber
bigNumber = HUGE(bigNumber)
DO iTariff = 1, numTariff
!nativeTotalEnergy
monthVal = 0.0d0
DO jPeriod = 1, countPeriod
DO kMonth = 1, MaxNumMonths
monthVal(kMonth) = monthVal(kMonth) + tariff(iTariff)%gatherEnergy(jPeriod,kMonth)
END DO
END DO
econVar(tariff(iTariff)%nativeTotalEnergy)%values = monthVal
!nativeTotalDemand
monthVal = -bigNumber
DO jPeriod = 1, countPeriod
DO kMonth = 1, MaxNumMonths
IF (tariff(iTariff)%gatherDemand(jPeriod,kMonth) .GT. monthVal(kMonth)) THEN
monthVal(kMonth) = tariff(iTariff)%gatherDemand(jPeriod,kMonth)
END IF
END DO
END DO
!if no maximum was set just set to zero
DO kMonth = 1, MaxNumMonths
IF (monthVal(kMonth) .EQ. -bigNumber) THEN
monthVal(kMonth) = 0.0d0
END IF
END DO
econVar(tariff(iTariff)%nativeTotalDemand)%values = monthVal
DO kMonth = 1, MaxNumMonths
!nativePeakEnergy
econVar(tariff(iTariff)%nativePeakEnergy)%values(kMonth) = tariff(iTariff)%gatherEnergy(periodPeak,kMonth)
!nativePeakDemand
econVar(tariff(iTariff)%nativePeakDemand)%values(kMonth) = tariff(iTariff)%gatherDemand(periodPeak,kMonth)
!nativeShoulderEnergy
econVar(tariff(iTariff)%nativeShoulderEnergy)%values(kMonth) = tariff(iTariff)%gatherEnergy(periodShoulder,kMonth)
!nativeShoulderDemand
econVar(tariff(iTariff)%nativeShoulderDemand)%values(kMonth) = tariff(iTariff)%gatherDemand(periodShoulder,kMonth)
!nativeOffPeakEnergy
econVar(tariff(iTariff)%nativeOffPeakEnergy)%values(kMonth) = tariff(iTariff)%gatherEnergy(periodOffPeak,kMonth)
!nativeOffPeakDemand
econVar(tariff(iTariff)%nativeOffPeakDemand)%values(kMonth) = tariff(iTariff)%gatherDemand(periodOffPeak,kMonth)
!nativeMidPeakEnergy
econVar(tariff(iTariff)%nativeMidPeakEnergy)%values(kMonth) = tariff(iTariff)%gatherEnergy(periodMidPeak,kMonth)
!nativeMidPeakDemand
econVar(tariff(iTariff)%nativeMidPeakDemand)%values(kMonth) = tariff(iTariff)%gatherDemand(periodMidPeak,kMonth)
!nativePeakExceedsOffPeak
monthVal(kMonth) = tariff(iTariff)%gatherDemand(periodPeak,kMonth) - tariff(iTariff)%gatherDemand(periodOffPeak,kMonth)
IF (monthVal(kMonth) .GT. 0) THEN
econVar(tariff(iTariff)%nativePeakExceedsOffPeak)%values(kMonth) = monthVal(kMonth)
ELSE
econVar(tariff(iTariff)%nativePeakExceedsOffPeak)%values(kMonth) = 0.0d0
ENDIF
!nativeOffPeakExceedsPeak
monthVal(kMonth) = tariff(iTariff)%gatherDemand(periodOffPeak,kMonth) - tariff(iTariff)%gatherDemand(periodPeak,kMonth)
IF (monthVal(kMonth) .GT. 0) THEN
econVar(tariff(iTariff)%nativeOffPeakExceedsPeak)%values(kMonth) = monthVal(kMonth)
ELSE
econVar(tariff(iTariff)%nativeOffPeakExceedsPeak)%values(kMonth) = 0.0d0
ENDIF
!nativePeakExceedsMidPeak
monthVal(kMonth) = tariff(iTariff)%gatherDemand(periodPeak,kMonth) - tariff(iTariff)%gatherDemand(periodMidPeak,kMonth)
IF (monthVal(kMonth) .GT. 0) THEN
econVar(tariff(iTariff)%nativePeakExceedsMidPeak)%values(kMonth) = monthVal(kMonth)
ELSE
econVar(tariff(iTariff)%nativePeakExceedsOffPeak)%values(kMonth) = 0.0d0
ENDIF
!nativeMidPeakExceedsPeak
monthVal(kMonth) = tariff(iTariff)%gatherDemand(periodMidPeak,kMonth) - tariff(iTariff)%gatherDemand(periodPeak,kMonth)
IF (monthVal(kMonth) .GT. 0) THEN
econVar(tariff(iTariff)%nativeMidPeakExceedsPeak)%values(kMonth) = monthVal(kMonth)
ELSE
econVar(tariff(iTariff)%nativeMidPeakExceedsPeak)%values(kMonth) = 0.0d0
ENDIF
!nativePeakExceedsShoulder
monthVal(kMonth) = tariff(iTariff)%gatherDemand(periodPeak,kMonth) - tariff(iTariff)%gatherDemand(periodShoulder,kMonth)
IF (monthVal(kMonth) .GT. 0) THEN
econVar(tariff(iTariff)%nativePeakExceedsShoulder)%values(kMonth) = monthVal(kMonth)
ELSE
econVar(tariff(iTariff)%nativePeakExceedsShoulder)%values(kMonth) = 0.0d0
ENDIF
!nativeShoulderExceedsPeak
monthVal(kMonth) = tariff(iTariff)%gatherDemand(periodShoulder,kMonth) - tariff(iTariff)%gatherDemand(periodPeak,kMonth)
IF (monthVal(kMonth) .GT. 0) THEN
econVar(tariff(iTariff)%nativeShoulderExceedsPeak)%values(kMonth) = monthVal(kMonth)
ELSE
econVar(tariff(iTariff)%nativeShoulderExceedsPeak)%values(kMonth) = 0.0d0
ENDIF
!nativeIsWinter
!nativeIsNotWinter
IF (tariff(iTariff)%seasonForMonth(kMonth) .EQ. seasonWinter) THEN
econVar(tariff(iTariff)%nativeIsWinter)%values(kMonth) = 1.0d0
econVar(tariff(iTariff)%nativeIsNotWinter)%values(kMonth) = 0.0d0
ELSE
econVar(tariff(iTariff)%nativeIsWinter)%values(kMonth) = 0.0d0
econVar(tariff(iTariff)%nativeIsNotWinter)%values(kMonth) = 1.0d0
END IF
!nativeIsSpring
!nativeIsNotSpring
IF (tariff(iTariff)%seasonForMonth(kMonth) .EQ. seasonSpring) THEN
econVar(tariff(iTariff)%nativeIsSpring)%values(kMonth) = 1.0d0
econVar(tariff(iTariff)%nativeIsNotSpring)%values(kMonth) = 0.0d0
ELSE
econVar(tariff(iTariff)%nativeIsSpring)%values(kMonth) = 0.0d0
econVar(tariff(iTariff)%nativeIsNotSpring)%values(kMonth) = 1.0d0
END IF
!nativeIsSummer
!nativeIsNotSummer
IF (tariff(iTariff)%seasonForMonth(kMonth) .EQ. seasonSummer) THEN
econVar(tariff(iTariff)%nativeIsSummer)%values(kMonth) = 1.0d0
econVar(tariff(iTariff)%nativeIsNotSummer)%values(kMonth) = 0.0d0
ELSE
econVar(tariff(iTariff)%nativeIsSummer)%values(kMonth) = 0.0d0
econVar(tariff(iTariff)%nativeIsNotSummer)%values(kMonth) = 1.0d0
END IF
!nativeIsAutumn
!nativeIsNotAutumn
IF (tariff(iTariff)%seasonForMonth(kMonth) .EQ. seasonFall) THEN
econVar(tariff(iTariff)%nativeIsAutumn)%values(kMonth) = 1.0d0
econVar(tariff(iTariff)%nativeIsNotAutumn)%values(kMonth) = 0.0d0
ELSE
econVar(tariff(iTariff)%nativeIsAutumn)%values(kMonth) = 0.0d0
econVar(tariff(iTariff)%nativeIsNotAutumn)%values(kMonth) = 1.0d0
END IF
!nativePeakAndShoulderEnergy
econVar(tariff(iTariff)%nativePeakAndShoulderEnergy)%values(kMonth) = &
tariff(iTariff)%gatherEnergy(periodPeak,kMonth) + tariff(iTariff)%gatherEnergy(periodShoulder,kMonth)
!nativePeakAndShoulderDemand
IF (tariff(iTariff)%gatherDemand(periodPeak,kMonth) .GT. tariff(iTariff)%gatherDemand(periodShoulder,kMonth)) THEN
econVar(tariff(iTariff)%nativePeakAndShoulderDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodPeak,kMonth)
ELSE
econVar(tariff(iTariff)%nativePeakAndShoulderDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodShoulder,kMonth)
END IF
!nativePeakAndMidPeakEnergy
econVar(tariff(iTariff)%nativePeakAndMidPeakEnergy)%values(kMonth) = &
tariff(iTariff)%gatherEnergy(periodPeak,kMonth) + tariff(iTariff)%gatherEnergy(periodMidPeak,kMonth)
!nativePeakAndMidPeakDemand
IF (tariff(iTariff)%gatherDemand(periodPeak,kMonth) .GT. tariff(iTariff)%gatherDemand(periodMidPeak,kMonth)) THEN
econVar(tariff(iTariff)%nativePeakAndMidPeakDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodPeak,kMonth)
ELSE
econVar(tariff(iTariff)%nativePeakAndMidPeakDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodMidPeak,kMonth)
END IF
!nativeShoulderAndOffPeakEnergy
econVar(tariff(iTariff)%nativeShoulderAndOffPeakEnergy)%values(kMonth) = &
tariff(iTariff)%gatherEnergy(periodShoulder,kMonth) + tariff(iTariff)%gatherEnergy(periodOffPeak,kMonth)
!nativeShoulderAndOffPeakDemand
IF (tariff(iTariff)%gatherDemand(periodShoulder,kMonth) .GT. tariff(iTariff)%gatherDemand(periodOffPeak,kMonth)) THEN
econVar(tariff(iTariff)%nativeShoulderAndOffPeakDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodShoulder,kMonth)
ELSE
econVar(tariff(iTariff)%nativeShoulderAndOffPeakDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodOffPeak,kMonth)
END IF
!nativePeakAndOffPeakEnergy
econVar(tariff(iTariff)%nativePeakAndOffPeakEnergy)%values(kMonth) = &
tariff(iTariff)%gatherEnergy(periodPeak,kMonth) + tariff(iTariff)%gatherEnergy(periodOffPeak,kMonth)
!nativePeakAndOffPeakDemand
IF (tariff(iTariff)%gatherDemand(periodPeak,kMonth) .GT. tariff(iTariff)%gatherDemand(periodOffPeak,kMonth)) THEN
econVar(tariff(iTariff)%nativePeakAndOffPeakDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodPeak,kMonth)
ELSE
econVar(tariff(iTariff)%nativePeakAndOffPeakDemand)%values(kMonth) = &
tariff(iTariff)%gatherDemand(periodOffPeak,kMonth)
END IF
!nativeRealTimePriceCosts
econVar(tariff(iTariff)%nativeRealTimePriceCosts)%values(kMonth) = tariff(iTariff)%RTPcost(kMonth)
!nativeAboveCustomerBaseCosts
econVar(tariff(iTariff)%nativeAboveCustomerBaseCosts)%values(kMonth) = tariff(iTariff)%RTPaboveBaseCost(kMonth)
!nativeBelowCustomerBaseCosts
econVar(tariff(iTariff)%nativeBelowCustomerBaseCosts)%values(kMonth) = tariff(iTariff)%RTPbelowBaseCost(kMonth)
!nativeAboveCustomerBaseEnergy
econVar(tariff(iTariff)%nativeAboveCustomerBaseEnergy)%values(kMonth) = tariff(iTariff)%RTPaboveBaseEnergy(kMonth)
!nativeBelowCustomerBaseEnergy
econVar(tariff(iTariff)%nativeBelowCustomerBaseEnergy)%values(kMonth) = tariff(iTariff)%RTPbelowBaseEnergy(kMonth)
END DO
END DO
END SUBROUTINE setNativeVariables