Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | NumTUInList | |||
real(kind=r64), | intent(in) | :: | TotalCapacity | |||
real(kind=r64), | intent(in), | DIMENSION(:) | :: | CapArray | ||
real(kind=r64), | intent(inout) | :: | MaxLimit |
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 LimitCoilCapacity(NumTUInList,TotalCapacity,CapArray,MaxLimit)
! SUBROUTINE INFORMATION:
! AUTHOR Richard Raustad
! DATE WRITTEN July 2012 (Moved from InitVRF)
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculate the maximum allowed terminal unit capacity. Total terminal unit capacity must not
! exceed the available condenser capacity. This variable, MaxCapacity (passed out to MaxCoolingCapacity
! or MaxHeatingCapacity), is used to limit the terminal units providing more capacity than allowed.
! Example: TU loads are 1-ton, 2-ton, 3-ton, and 4-ton connected to a condenser having only 9-tons available.
! This variable is will be set to 3-tons and the 4-ton terminal unit will be limited to 3-tons
! (see InitVRF where this variable is reset and CalcVRF where the call to the DX coils passes this argument).
! METHODOLOGY EMPLOYED:
! The coils are simulated and summed. This value is compared to the available capacity. If the summed
! TU capacity is greater than the available capacity, limit the TU's with the highest capacity so that
! the TU capacity equals the available capacity. The report variable Variable Refrigerant Flow Heat Pump
! Maximum Terminal Unit Cool/Heating Capacity holds the value for maximum TU capacity. This value may not
! match the maximum individual coil capacity exactly since the available capaity uses a load weighted
! average WB temperature to calculate available capacity. When the TU's are limited, this weighting changes.
! The extra iterations required for these values to converge is considered excessive.
! If the globabl flag SimZoneEquipment could be set for 1 additional iteration, these variables would
! converge more closely (setting this globabl flag is not yet implemented).
! REFERENCES:
! na
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: NumTUInList ! Number of terminal units in list
REAL(r64), INTENT (IN) :: TotalCapacity ! temporary variable holding condenser capacity [W]
REAL(r64),DIMENSION(:), INTENT (IN) :: CapArray ! Array of coil capacities in either cooling or heating mode [W]
REAL(r64), INTENT (INOUT) :: MaxLimit ! Maximum terminal unit capacity for coils in same operating mode [W]
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: NumTU ! loop counter
INTEGER :: TempTUIndex ! temp variable used to find max terminal unit limit
INTEGER :: MinOutputIndex ! index to TU with lowest load
REAL(r64) :: MinOutput ! used when finding TU "max" capacity limit
REAL(r64) :: RemainingCapacity ! decrement capacity counter to find limiting TU capacity [W]
REAL(r64), ALLOCATABLE :: Temp(:) ! temporarary array for processing terminal units
REAL(r64), ALLOCATABLE :: Temp2(:) ! temporarary array for processing terminal units
ALLOCATE(Temp(NumTUInList))
ALLOCATE(Temp2(NumTUInList))
Temp = CapArray
Temp2 = Temp
RemainingCapacity = TotalCapacity
! sort TU capacity from lowest to highest
DO TempTUIndex = 1, NumTUInList
MinOutput = MaxCap
DO NumTU = 1, NumTUInList
IF(Temp2(NumTU) .LT. MinOutput)THEN
MinOutput = Temp2(NumTU)
Temp(TempTUIndex) = MinOutput
MinOutputIndex = NumTU
END IF
END DO
Temp2(MinOutputIndex) = MaxCap
END DO
! find limit of "terminal unit" capacity so that sum of all TU's does not exceed condenser capacity
! if the terminal unit capacity multiplied by number of remaining TU's does not exceed remaining available, subtract and cycle
DO TempTUIndex = 1, NumTUInList
IF((Temp(TempTUIndex)*(NumTUInList-TempTUIndex+1)) .LT. RemainingCapacity)THEN
RemainingCapacity = RemainingCapacity - Temp(TempTUIndex)
CYCLE
ELSE
! if it does exceed, limit is found
MaxLimit = RemainingCapacity / (NumTUInList-TempTUIndex+1)
EXIT
END IF
END DO
DEALLOCATE(Temp)
DEALLOCATE(Temp2)
RETURN
END SUBROUTINE LimitCoilCapacity