Nodes of different colours represent the following:
Solid arrows point from a parent (sub)module to the submodule which is descended from it. Dashed arrows point from a module being used to the module or program unit using it. Where possible, edges connecting nodes are given different colours to make them easier to distinguish in large graphs.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | WindACNum | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
integer, | intent(in) | :: | OpMode | |||
real(kind=r64), | intent(in) | :: | QZnReq | |||
real(kind=r64), | intent(out) | :: | PartLoadFrac | |||
logical, | intent(inout) | :: | HXUnitOn |
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.
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 ControlCycWindACOutput(WindACNum,FirstHVACIteration,OpMode,QZnReq,PartLoadFrac, HXUnitOn)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Buhl
! DATE WRITTEN May 2000
! MODIFIED Shirey, May 2001
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Determine the part load fraction of the air conditioner for this time step
! METHODOLOGY EMPLOYED:
! Linear interpolation between max and min outputs
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: TrimSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT (IN) :: WindACNum ! Unit index in fan coil array
LOGICAL, INTENT (IN) :: FirstHVACIteration ! flag for 1st HVAV iteration in the time step
INTEGER, INTENT(IN) :: OpMode ! operating mode: CycFanCycCoil | ContFanCycCoil
REAL(r64) , INTENT(IN) :: QZnReq ! cooling output needed by zone [W]
REAL(r64) , INTENT (OUT) :: PartLoadFrac ! unit part load fraction
LOGICAL, INTENT (INOUT) :: HXUnitOn ! Used to control HX heat recovery as needed
! SUBROUTINE PARAMETER DEFINITIONS:
!
INTEGER, PARAMETER :: MaxIter = 50 !maximum number of iterations
REAL(r64), PARAMETER :: MinPLF = 0.0d0 !minimum part load factor allowed
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: FullOutput ! unit full output [W]
REAL(r64) :: NoCoolOutput ! output when no active cooling [W]
REAL(r64) :: ActualOutput ! output at current partloadfrac [W]
REAL(r64) :: Error ! error between QznReq and ActualOutput [W]
REAL(r64) :: ErrorToler ! error tolerance
INTEGER :: Iter ! iteration counter
!CHARACTER(len=20) :: ErrNum
!INTEGER,SAVE :: ErrCount=0
REAL(r64) :: DelPLF
REAL(r64) :: Relax
! DX Cooling HX assisted coils can cycle the heat exchanger, see if coil ON, HX OFF can meet humidity setpoint if one exists
IF(WindAC(WindACNum)%DXCoilType_Num == CoilDX_CoolingHXAssisted)THEN
! Check for a setpoint at the HX outlet node, if it doesn't exist always run the HX
IF(Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRatMax .EQ. SensedNodeFlagValue) THEN
HXUnitOn = .TRUE.
ELSE
HXUnitOn = .FALSE.
END IF
ELSE
HXUnitOn = .FALSE.
END IF
IF (WindAC(WindACNum)%EMSOverridePartLoadFrac) THEN
PartLoadFrac = WindAC(WindACNum)%EMSValueForPartLoadFrac
ENDIF
! Get result when DX coil is off
CALL CalcWindowACOutput(WindACNum,FirstHVACIteration,OpMode,0.0d0,HXUnitOn,NoCoolOutput)
! If NoCoolOutput < QZnReq, the coil needs to be off
IF (NoCoolOutput < QZnReq) THEN
PartLoadFrac = 0.0d0
RETURN
END IF
! Get full load result
CALL CalcWindowACOutput(WindACNum,FirstHVACIteration,OpMode,1.0d0,HXUnitOn,FullOutput)
! Since we are cooling, we expect FullOutput to be < 0 and FullOutput < NoCoolOutput
! Check that this is the case; if not set PartLoadFrac = 0.0 (off) and return
IF (FullOutput >= 0.0d0 .OR. FullOutput >= NoCoolOutput) THEN
PartLoadFrac = 0.0d0
RETURN
END IF
! If the QZnReq <= FullOutput the unit needs to run full out
IF (QZnReq <= FullOutput .AND. WindAC(WindACNum)%DXCoilType_Num /= CoilDX_CoolingHXAssisted) THEN
PartLoadFrac = 1.0d0
RETURN
END IF
! If the QZnReq <= FullOutput and a HXAssisted coil is used, check the node setpoint for a maximum humidity ratio set piont
! HumRatMax will either equal -999 if no setpoint exists or could be 0 if no moisture load is present
IF (QZnReq <= FullOutput .AND. WindAC(WindACNum)%DXCoilType_Num == CoilDX_CoolingHXAssisted .AND. &
Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRatMax .LE. 0.0d0) THEN
PartLoadFrac = 1.0d0
RETURN
END IF
! QZnReq should now be greater than FullOutput and less than NoCoolOutput)
! Calculate the part load fraction
PartLoadFrac = MAX(MinPLF, ABS(QZnReq - NoCoolOutput) / ABS(FullOutput - NoCoolOutput))
ErrorToler = WindAC(WindACNum)%ConvergenceTol !Error tolerance for convergence from input deck
Error = 1.0d0 !initialize error value for comparison against tolerance
Iter = 0 !initialize iteration counter
Relax = 1.0d0
DO WHILE ((ABS(Error) .GT. ErrorToler) .AND. (Iter .LE. MaxIter) .AND. PartLoadFrac .GT. MinPLF)
! Get result when DX coil is operating at partloadfrac
CALL CalcWindowACOutput(WindACNum,FirstHVACIteration,OpMode,PartLoadFrac,HXUnitOn,ActualOutput)
Error = (QZnReq - ActualOutput)/QZnReq
DelPLF = (QZnReq-ActualOutput)/FullOutput
PartLoadFrac = PartLoadFrac + Relax * DelPLF
PartLoadFrac = MAX(MinPLF,MIN(1.0d0,PartLoadFrac))
Iter = Iter + 1
IF (Iter == 16) THEN
Relax = 0.5d0
END IF
END DO
IF (Iter .GT. MaxIter) THEN
IF (WindAC(WindACNum)%MaxIterIndex1 == 0) THEN
CALL ShowWarningMessage('ZoneHVAC:WindowAirConditioner="'//TRIM(WindAC(WindACNum)%Name)// &
'" -- Exceeded max iterations while adjusting compressor'// &
' sensible runtime to meet the zone load within the cooling convergence tolerance.')
CALL ShowContinueErrorTimeStamp('Iterations='//TRIM(TrimSigDigits(MaxIter)))
ENDIF
CALL ShowRecurringWarningErrorAtEnd('ZoneHVAC:WindowAirConditioner="'//TRIM(WindAC(WindACNum)%Name)// &
'" -- Exceeded max iterations error (sensible runtime) continues...',WindAC(WindACNum)%MaxIterIndex1)
END IF
IF(WindAC(WindACNum)%DXCoilType_Num == CoilDX_CoolingHXAssisted .AND. &
Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRatMax .LT. Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRat .AND. &
Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRatMax .GT. 0.0d0) THEN
! Run the HX to recovery energy and improve latent performance
HXUnitOn = .TRUE.
! Get full load result
CALL CalcWindowACOutput(WindACNum,FirstHVACIteration,OpMode,1.0d0,HXUnitOn,FullOutput)
IF(Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRatMax .LT. Node(WindAC(WindACNum)%CoilOutletNodeNum)%HumRat .OR. &
QZnReq <= FullOutput) THEN
PartLoadFrac = 1.0d0
RETURN
END IF
Error = 1.0d0 !initialize error value for comparison against tolerance
Iter = 0 !initialize iteration counter
Relax = 1.0d0
DO WHILE ((ABS(Error) .GT. ErrorToler) .AND. (Iter .LE. MaxIter) .AND. PartLoadFrac .GT. MinPLF)
! Get result when DX coil is operating at partloadfrac
CALL CalcWindowACOutput(WindACNum,FirstHVACIteration,OpMode,PartLoadFrac,HXUnitOn,ActualOutput)
Error = (QZnReq - ActualOutput)/QZnReq
DelPLF = (QZnReq-ActualOutput)/FullOutput
PartLoadFrac = PartLoadFrac + Relax * DelPLF
PartLoadFrac = MAX(MinPLF,MIN(1.0d0,PartLoadFrac))
Iter = Iter + 1
IF (Iter == 16) THEN
Relax = 0.5d0
END IF
END DO
IF (Iter .GT. MaxIter) THEN
IF (WindAC(WindACNum)%MaxIterIndex2 == 0) THEN
CALL ShowWarningMessage('ZoneHVAC:WindowAirConditioner="'//TRIM(WindAC(WindACNum)%Name)// &
'" -- Exceeded max iterations while adjusting compressor'// &
' latent runtime to meet the zone load within the cooling convergence tolerance.')
CALL ShowContinueErrorTimeStamp('Iterations='//TRIM(TrimSigDigits(MaxIter)))
ENDIF
CALL ShowRecurringWarningErrorAtEnd('ZoneHVAC:WindowAirConditioner="'//TRIM(WindAC(WindACNum)%Name)// &
'" -- Exceeded max iterations error (latent runtime) continues...',WindAC(WindACNum)%MaxIterIndex2)
END IF
END IF ! WindAC(WindACNum)%DXCoilType_Num == CoilDX_CoolingHXAssisted .AND. &
RETURN
END SUBROUTINE ControlCycWindACOutput