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) | :: | ControlNum | |||
logical, | intent(in) | :: | FirstHVACIteration | |||
logical, | intent(inout) | :: | IsConvergedFlag |
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 InitController(ControlNum,FirstHVACIteration,IsConvergedFlag)
! SUBROUTINE INFORMATION:
! AUTHOR Richard J. Liesen
! DATE WRITTEN July 1998
! MODIFIED Shirey/Raustad (FSEC), Jan 2004
! MODIFIED Dimitri Curtil (LBNL), Feb 2006
! - Moved first call convergence test code to ResetController()
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine is for initializations of the Controller Components.
! METHODOLOGY EMPLOYED:
! Uses the status flags to trigger events.
! REFERENCES:
! na
! USE STATEMENTS:
USE Psychrometrics, ONLY: PsyTdpFnWPb
USE FluidProperties, ONLY: GetDensityGlycol
USE DataEnvironment, ONLY: OutBaroPress
USE DataHVACGlobals, ONLY: DoSetPointTest
USE RootFinder, ONLY: SetupRootFinder
USE EMSManager, ONLY: iTemperatureSetpoint, CheckIfNodeSetpointManagedByEMS , &
iHumidityRatioSetpoint, iHumidityRatioMaxSetpoint, iMassFlowRateSetpoint
USE DataPlant, ONLY: PlantLoop, ScanPlantLoopsForNodeNum
USE PlantUtilities, ONLY: SetActuatedBranchFlowRate
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ControlNum
LOGICAL, INTENT(INOUT) :: IsConvergedFlag
LOGICAL, INTENT(IN) :: FirstHVACIteration ! TRUE if first full HVAC iteration in an HVAC timestep
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ActuatedNode
INTEGER :: SensedNode
INTEGER :: ControllerIndex
LOGICAL, SAVE :: MyOneTimeFlag = .TRUE.
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyEnvrnFlag
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MySizeFlag
LOGICAL, ALLOCATABLE, SAVE, DIMENSION(:) :: MyPlantIndexsFlag
LOGICAL, SAVE :: MySetPointCheckFlag = .TRUE.
! Supply Air Temp Setpoint when 'TemperatureAndHumidityRatio' control is used
REAL(r64), SAVE :: HumidityControlTempSetPoint
! Difference between SA dry-bulb and dew-point temperatures
REAL(r64) :: ApproachTemp
! Desired dew point temperature setpoint for 'TemperatureAndHumidityRatio' control
REAL(r64) :: DesiredDewPoint
REAL(r64) :: rho !local fluid density
IF (MyOneTimeFlag) THEN
ALLOCATE(MyEnvrnFlag(NumControllers))
ALLOCATE(MySizeFlag(NumControllers))
ALLOCATE(MyPlantIndexsFlag(NumControllers))
MyEnvrnFlag = .TRUE.
MySizeFlag = .TRUE.
MyPlantIndexsFlag = .TRUE.
MyOneTimeFlag = .FALSE.
END IF
IF ( .NOT. SysSizingCalc .AND. MySetPointCheckFlag .AND. DoSetPointTest) THEN
! check for missing setpoints
DO ControllerIndex=1,NumControllers
SensedNode = ControllerProps(ControllerIndex)%SensedNode
SELECT CASE(ControllerProps(ControllerIndex)%ControlVar)
CASE(iTemperature) ! 'Temperature'
IF (Node(SensedNode)%TempSetPoint == SensedNodeFlagValue) THEN
IF (.NOT. AnyEnergyManagementSystemInModel) THEN
CALL ShowSevereError('HVACControllers: Missing temperature setpoint for controller type='// &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (by Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a Setpoint Manager with Control Variable = "Temperature" to establish '// &
'a setpoint at the controller sensed node.')
SetPointErrorFlag = .TRUE.
ELSE
! call to check node is actuated by EMS
CALL CheckIfNodeSetpointManagedByEMS(SensedNode,iTemperatureSetpoint, SetpointErrorFlag)
IF (SetpointErrorFlag) THEN
CALL ShowSevereError ('HVACControllers: Missing temperature setpoint for controller type='// &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (by Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a Setpoint Manager with Control Variable = "Temperature" to establish '// &
'a setpoint at the controller sensed node.')
CALL ShowContinueError('Or add EMS Actuator to provide temperature setpoint at this node')
ENDIF
ENDIF
ELSE
! Warn if humidity setpoint is detected (only for cooling coils) and control varible is TEMP.
IF (Node(SensedNode)%HumRatMax /= SensedNodeFlagValue .AND. &
ControllerProps(ControllerIndex)%Action==iReverseAction) THEN
CALL ShowWarningError('HVACControllers: controller type='//TRIM(ControllerProps(ControllerIndex)%ControllerType)// &
' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"'// &
' has detected a maximum humidity ratio setpoint at the control node.')
CALL ShowContinueError('Node referenced (by controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' set the controller control variable to TemperatureAndHumidityRatio' &
//' if humidity control is desired.')
! SetPointErrorFlag = .TRUE.
END IF
END IF
CASE(iHumidityRatio) ! 'HumidityRatio'
IF (Node(SensedNode)%HumRatSetPoint == SensedNodeFlagValue) THEN
IF (.NOT. AnyEnergyManagementSystemInModel) THEN
CALL ShowSevereError('HVACControllers: Missing humidity ratio setpoint for controller type=' // &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node referenced (by controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a SetpointManager with the field Control Variable = "HumidityRatio" to establish '// &
'a setpoint at the controller sensed node.')
SetPointErrorFlag = .TRUE.
ELSE
CALL CheckIfNodeSetpointManagedByEMS(SensedNode,iHumidityRatioSetpoint, SetpointErrorFlag)
IF (SetpointErrorFlag) THEN
CALL ShowSevereError('HVACControllers: Missing humidity ratio setpoint for controller type=' // &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node referenced (by controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a SetpointManager with the field Control Variable = '// &
'"HumidityRatio" to establish a setpoint at the controller sensed node.')
CALL ShowContinueError('Or add EMS Actuator to provide Humidity Ratio setpoint at this node')
ENDIF
ENDIF
END IF
CASE(iTemperatureAndHumidityRatio) ! 'TemperatureAndHumidityRatio'
IF (Node(SensedNode)%TempSetPoint == SensedNodeFlagValue) THEN
IF (.NOT. AnyEnergyManagementSystemInModel) THEN
CALL ShowSevereError('HVACControllers: Missing temperature setpoint for controller type='// &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (by Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a Setpoint Manager with Control Variable = "Temperature" to establish '// &
'a setpoint at the controller sensed node.')
SetPointErrorFlag = .TRUE.
ELSE
! call to check node is actuated by EMS
CALL CheckIfNodeSetpointManagedByEMS(SensedNode,iTemperatureSetpoint, SetpointErrorFlag)
IF (SetpointErrorFlag) THEN
CALL ShowSevereError ('HVACControllers: Missing temperature setpoint for controller type='// &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (by Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a Setpoint Manager with Control Variable = "Temperature" to establish '// &
'a setpoint at the controller sensed node.')
CALL ShowContinueError('Or add EMS Actuator to provide temperature setpoint at this node')
ENDIF
ENDIF
END IF
IF (Node(SensedNode)%HumRatMax == SensedNodeFlagValue) THEN
IF (.NOT. AnyEnergyManagementSystemInModel) THEN
CALL ShowSevereError('HVACControllers: Missing maximum humidity ratio setpoint for controller type=' // &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (by Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a SetpointManager with the field Control Variable = '// &
'"MaximumHumidityRatio" to establish a setpoint at the controller sensed node.')
SetPointErrorFlag = .TRUE.
ELSE
! call to check node is actuated by EMS
CALL CheckIfNodeSetpointManagedByEMS(SensedNode,iHumidityRatioMaxSetpoint, SetpointErrorFlag)
IF (SetpointErrorFlag) THEN
CALL ShowSevereError('HVACControllers: Missing maximum humidity ratio setpoint for controller type=' // &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (by Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a SetpointManager with the field Control Variable = '// &
'"MaximumHumidityRatio" to establish a setpoint at the controller sensed node.')
CALL ShowContinueError('Or add EMS Actuator to provide maximum Humidity Ratio setpoint at this node')
ENDIF
ENDIF
END IF
CASE(iFlow) ! 'Flow'
IF (Node(SensedNode)%MassFlowRateSetPoint == SensedNodeFlagValue) THEN
IF (.NOT. AnyEnergyManagementSystemInModel) THEN
CALL ShowSevereError('HVACControllers: Missing mass flow rate setpoint for controller type=' // &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (in Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a SetpointManager with the field Control Variable = "MassFlowRate" to establish '// &
'a setpoint at the controller sensed node.')
SetPointErrorFlag = .TRUE.
ELSE
! call to check node is actuated by EMS
CALL CheckIfNodeSetpointManagedByEMS(SensedNode,iMassFlowRateSetpoint, SetpointErrorFlag)
IF (SetpointErrorFlag) THEN
CALL ShowSevereError('HVACControllers: Missing mass flow rate setpoint for controller type=' // &
TRIM(ControllerProps(ControllerIndex)%ControllerType)//' Name="'// &
TRIM(ControllerProps(ControllerIndex)%ControllerName) // '"')
CALL ShowContinueError('Node Referenced (in Controller)='//TRIM(NodeID(SensedNode)))
CALL ShowContinueError(' use a SetpointManager with the field Control Variable = "MassFlowRate" to establish '// &
'a setpoint at the controller sensed node.')
CALL ShowContinueError('Or add EMS Actuator to provide Mass Flow Rate setpoint at this node')
ENDIF
ENDIF
END IF
END SELECT
END DO
MySetPointCheckFlag = .FALSE.
END IF
IF (ALLOCATED(PlantLoop) .AND. MyPlantIndexsFlag(ControlNum)) THEN
CALL ScanPlantLoopsForNodeNum(ControllerProps(ControlNum)%ControllerName, &
ControllerProps(ControlNum)%ActuatedNode, &
ControllerProps(ControlNum)%ActuatedNodePlantLoopNum, &
ControllerProps(ControlNum)%ActuatedNodePlantLoopSide, &
ControllerProps(ControlNum)%ActuatedNodePlantLoopBranchNum)
MyPlantIndexsFlag(ControlNum) = .FALSE.
ENDIF
IF ( .NOT. SysSizingCalc .AND. MySizeFlag(ControlNum)) THEN
CALL SizeController(ControlNum)
!Check to make sure that the Minimum Flow rate is less than the max.
IF (ControllerProps(ControlNum)%MaxVolFlowActuated == 0.0d0) THEN
ControllerProps(ControlNum)%MinVolFlowActuated = 0.0d0
ELSE IF (ControllerProps(ControlNum)%MinVolFlowActuated .GE. ControllerProps(ControlNum)%MaxVolFlowActuated) THEN
CALL ShowFatalError( &
'Controller:WaterCoil, Minimum control flow is > or = Maximum control flow; '// &
TRIM(ControllerProps(ControlNum)%ControllerName) &
)
END IF
! Setup root finder after sizing calculation
SelectAction: SELECT CASE ( ControllerProps(ControlNum)%Action )
CASE ( iNormalAction )
CALL SetupRootFinder( &
RootFinders(ControlNum), &
iSlopeIncreasing, & ! Slope type
iMethodBrent, & ! Method type
constant_zero, & ! TolX: no relative tolerance for X variables
1.0d-6, & ! ATolX: absolute tolerance for X variables
ControllerProps(ControlNum)%Offset & ! ATolY: absolute tolerance for Y variables
)
CASE ( iReverseAction )
CALL SetupRootFinder( &
RootFinders(ControlNum), &
iSlopeDecreasing, & ! Slope type
iMethodBrent, & ! Method type
constant_zero, & ! TolX: no relative tolerance for X variables
1.0d-6, & ! ATolX: absolute tolerance for X variables
ControllerProps(ControlNum)%Offset & ! ATolY: absolute tolerance for Y variables
)
CASE DEFAULT
CALL ShowFatalError( &
'InitController: Invalid controller action. '// &
'Valid choices are "Normal" or "Reverse"' &
)
END SELECT SelectAction
MySizeFlag(ControlNum) = .FALSE.
END IF
! Set the sensed and actuated node numbers
ActuatedNode = ControllerProps(ControlNum)%ActuatedNode
SensedNode = ControllerProps(ControlNum)%SensedNode
! Do the Begin Environment initializations
IF (BeginEnvrnFlag .AND. MyEnvrnFlag(ControlNum)) THEN
rho = GetDensityGlycol( PlantLoop(ControllerProps(ControlNum)%ActuatedNodePlantLoopNum)%FluidName, &
InitConvTemp, &
PlantLoop(ControllerProps(ControlNum)%ActuatedNodePlantLoopNum)%FluidIndex,&
'InitController')
ControllerProps(ControlNum)%MinActuated = rho*ControllerProps(ControlNum)%MinVolFlowActuated
ControllerProps(ControlNum)%MaxActuated = rho*ControllerProps(ControlNum)%MaxVolFlowActuated
! Turn off scheme to reuse previous solution obtained at last SimAirLoop() call
ControllerProps(ControlNum)%ReusePreviousSolutionFlag = .FALSE.
! Reset solution trackers
ControllerProps(ControlNum)%SolutionTrackers%DefinedFlag = .FALSE.
ControllerProps(ControlNum)%SolutionTrackers%Mode = iModeNone
ControllerProps(ControlNum)%SolutionTrackers%ActuatedValue = 0.0d0
MyEnvrnFlag(ControlNum) = .FALSE.
END IF
IF (.NOT. BeginEnvrnFlag) THEN
MyEnvrnFlag(ControlNum)=.TRUE.
ENDIF
Call SetActuatedBranchFlowRate(ControllerProps(ControlNum)%NextActuatedValue, &
ActuatedNode, &
ControllerProps(ControlNum)%ActuatedNodePlantLoopNum,&
ControllerProps(ControlNum)%ActuatedNodePlantLoopSide, &
ControllerProps(ControlNum)%ActuatedNodePlantLoopBranchNum, &
.FALSE.)
! Do the following initializations (every time step): This should be the info from
! the previous components outlets or the node data in this section.
! Load the node data in this section for the component simulation
IsConvergedFlag = .FALSE.
SELECT CASE(ControllerProps(ControlNum)%ControlVar)
CASE (iTemperature) ! 'Temperature'
ControllerProps(ControlNum)%SensedValue = Node(SensedNode)%Temp
! Done once per HVAC step
IF ( .NOT.ControllerProps(ControlNum)%IsSetPointDefinedFlag ) THEN
ControllerProps(ControlNum)%SetPointValue = Node(SensedNode)%TempSetPoint
ControllerProps(ControlNum)%IsSetPointDefinedFlag = .TRUE.
END IF
CASE (iTemperatureAndHumidityRatio) ! 'TemperatureAndHumidityRatio'
ControllerProps(ControlNum)%SensedValue = Node(SensedNode)%Temp
! Done once per HVAC step
!
! WARNING: The scheme for computing the setpoint for the dual temperature and humidity ratio
! control strategy breaks down whenever the sensed node temperature is modified by
! a controller fired after the current one. Indeed the final sensed node temperature
! is likely to have changed in the meantime if the other controller is active,
! thereby invalidating the setpoint calculation for the other controller performed
! earlier on the air loop.
!
IF ( .NOT.ControllerProps(ControlNum)%IsSetPointDefinedFlag ) THEN
! NOTE: For TEMPANDHUMRAT control the computed value ControllerProps(ControlNum)%SetPointValue
! depends on:
! - Node(SensedNode)%HumRatMax
! - Node(SensedNode)%Temp
! - Node(SensedNode)%HumRat
IF (Node(SensedNode)%HumRatMax .GT. 0) THEN
! Setpoint can only be computed when the sensed node temperature is evaluated at the max
! actuated value for the dual humidity ratio / temperature strategy.
! See routine CalcSimpleController() for the sequence of operations.
IF (ControllerProps(ControlNum)%NextActuatedValue == RootFinders(ControlNum)%MaxPoint%X) THEN
! Calculate the approach temperature (difference between SA dry-bulb temp and SA dew point temp)
ApproachTemp = Node(SensedNode)%Temp - PsyTdpFnWPb(Node(SensedNode)%HumRat,OutBaroPress)
! Calculate the dew point temperature at the SA humidity ratio setpoint
DesiredDewPoint = PsyTdpFnWPb(Node(SensedNode)%HumRatMax,OutBaroPress)
! Adjust the calculated dew point temperature by the approach temp
HumidityControlTempSetPoint = DesiredDewPoint + ApproachTemp
! NOTE: The next line introduces a potential discontinuity into the residual function
! which could prevent the root finder from finding the root it if were done at each
! controller iteration. For this reason we perform the setpoint calculation only
! once when the air loop has been evaluated with the max actuated value.
! See routine CalcSimpleController() for the sequence of operations.
ControllerProps(ControlNum)%SetPointValue = MIN( &
Node(SensedNode)%TempSetPoint, & ! Pure temperature setpoint
HumidityControlTempSetPoint & ! Temperature setpoint to achieve the humidity ratio setpoint
)
! Overwrite the "pure" temperature setpoint with the actual setpoint that takes into
! account the humidity ratio setpoint.
!
! NOTE: Check that this does not create side-effects somewhere else in the code.
Node(SensedNode)%TempSetPoint = ControllerProps(ControlNum)%SetPointValue
! Finally indicate thate the setpoint has been computed
ControllerProps(ControlNum)%IsSetPointDefinedFlag = .TRUE.
END IF
ELSE
! Pure temperature setpoint control strategy
ControllerProps(ControlNum)%SetPointValue = Node(SensedNode)%TempSetPoint
! Finally indicate thate the setpoint has been computed
ControllerProps(ControlNum)%IsSetPointDefinedFlag = .TRUE.
END IF
END IF
CASE(iHumidityRatio) ! 'HumidityRatio'
ControllerProps(ControlNum)%SensedValue = Node(SensedNode)%HumRat
! Done once per HVAC step
IF ( .NOT.ControllerProps(ControlNum)%IsSetPointDefinedFlag ) THEN
ControllerProps(ControlNum)%SetPointValue = Node(SensedNode)%HumRatSetPoint
ControllerProps(ControlNum)%IsSetPointDefinedFlag = .TRUE.
END IF
CASE(iFlow) ! 'Flow'
ControllerProps(ControlNum)%SensedValue = Node(SensedNode)%MassFlowRate
! Done once per HVAC step
IF ( .NOT.ControllerProps(ControlNum)%IsSetPointDefinedFlag ) THEN
ControllerProps(ControlNum)%SetPointValue = Node(SensedNode)%MassFlowRateSetPoint
ControllerProps(ControlNum)%IsSetPointDefinedFlag = .TRUE.
END IF
CASE DEFAULT
CALL ShowFatalError( &
'Invalid Controller Variable Type='// &
TRIM(ControlVariableTypes(ControllerProps(ControlNum)%ControlVar)) &
)
END SELECT
SELECT CASE(ControllerProps(ControlNum)%ActuatorVar)
CASE(iFlow) ! 'Flow'
! At the beginning of every time step the value is reset to the User Input
! The interface managers can reset the Max or Min to available values during the time step
! and these will then be the new setpoint limits for the controller to work within.
ControllerProps(ControlNum)%ActuatedValue = Node(ActuatedNode)%MassFlowRate
! Compute the currently available min and max bounds for controller.
! Done only once per HVAC step, as it would not make any sense to modify the min/max
! bounds during successive iterations of the root finder.
IF ( ControllerProps(ControlNum)%NumCalcCalls == 0 ) THEN
ControllerProps(ControlNum)%MinAvailActuated = MAX( &
Node(ActuatedNode)%MassFlowRateMinAvail, &
ControllerProps(ControlNum)%MinActuated)
ControllerProps(ControlNum)%MaxAvailActuated = MIN( &
Node(ActuatedNode)%MassFlowRateMaxAvail, &
ControllerProps(ControlNum)%MaxActuated)
! MinActuated is user input for minimum actuated flow, use that value if allowed
! (i.e., reset MinAvailActuated based on Node%MassFlowRateMaxAvail)
ControllerProps(ControlNum)%MinAvailActuated = MIN( &
ControllerProps(ControlNum)%MinAvailActuated, &
ControllerProps(ControlNum)%MaxAvailActuated)
END IF
CASE DEFAULT
CALL ShowFatalError( &
'Invalid Actuator Variable Type='// &
TRIM(ControlVariableTypes(ControllerProps(ControlNum)%ActuatorVar)) &
)
END SELECT
! Compute residual for control function using desired setpoint value and current sensed value
!
! NOTE: The delta sensed value might be wrong if the setpoint has not yet been computed.
! Make sure not to use it until the setpoint has been computed.
IF ( ControllerProps(ControlNum)%IsSetPointDefinedFlag ) THEN
ControllerProps(ControlNum)%DeltaSensed = ControllerProps(ControlNum)%SensedValue &
- ControllerProps(ControlNum)%SetPointValue
ELSE
ControllerProps(ControlNum)%DeltaSensed = 0.0d0
ENDIF
RETURN
END SUBROUTINE InitController