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), | optional | :: | PNum | ||
real(kind=r64), | intent(in), | optional | :: | Tset | ||
real(kind=r64), | intent(out), | optional | :: | PMVResult |
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 CalcThermalComfortFanger(PNum,Tset,PMVResult)
! SUBROUTINE INFORMATION:
! AUTHOR Jaewook Lee
! DATE WRITTEN January 2000
! MODIFIED Rick Strand (for E+ implementation February 2000)
! Brent Griffith modifications for CR 5641 (October 2005)
! L. Gu, Added optional arguments for thermal comfort control (May 2006)
! T. Hong, added Fanger PPD (April 2009)
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates PMV(Predicted Mean Vote) using the Fanger thermal
! comfort model. This subroutine is also used for thermal comfort control by determining
! the temperature at which the PMV is equal to a PMV setpoint specified by the user.
! METHODOLOGY EMPLOYED:
! This subroutine is based heavily upon the work performed by Dan Maloney for
! the BLAST program. Many of the equations are based on the original Fanger
! development. See documentation for further details and references.
! REFERENCES:
! Maloney, Dan, M.S. Thesis, University of Illinois at Urbana-Champaign
!
! BG note (10/21/2005), This formulation is based on the the BASIC program
! that is included in ASHRAE Standard 55 Normative Appendix D.
!
! USE STATEMENTS:
USE Psychrometrics, ONLY:PsyPsatFnTemp
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN), OPTIONAL :: PNum ! People number for thermal comfort control
REAL(r64), INTENT(IN), OPTIONAL :: Tset ! Temperature setpoint for thermal comfort control
REAL(r64), INTENT(OUT), OPTIONAL :: PMVResult ! PMV value for thermal comfort control
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: MaxIter = 150 ! Limit of iteration
REAL(r64), PARAMETER :: StopIterCrit = 0.00015d0 ! Stop criteria for iteration
REAL(r64), PARAMETER :: SkinEmiss = 0.97d0 ! Emissivity of clothing-skin surface
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: P1 ! Intermediate variables to calculate clothed body ratio and clothing temperature
REAL(r64) :: P2 ! Intermediate variables to calculate clothed body ratio and clothing temperature
REAL(r64) :: P3 ! Intermediate variables to calculate clothed body ratio and clothing temperature
REAL(r64) :: P4 ! Intermediate variables to calculate clothed body ratio and clothing temperature
REAL(r64) :: XF ! Intermediate variables to calculate clothed body ratio and clothing temperature
REAL(r64) :: XN ! Intermediate variables to calculate clothed body ratio and clothing temperature
REAL(r64) :: IntermediateClothing
! REAL(r64) :: SkinTempComf ! Skin temperature required to achieve thermal comfort; C
REAL(r64) :: PMV ! temporary variable to store calculated Fanger PMV value
REAL(r64) :: PPD ! temporary variable to store calculated Fanger PPD value
DO PeopleNum = 1, TotPeople
! Optional argument is used to access people object when thermal comfort control is used
If (PRESENT(PNum)) then
If (PeopleNum .NE. PNum) Cycle
End If
! If optional argument is used do not cycle regardless of thermal comfort reporting type
IF((.NOT. People(PeopleNum)%Fanger) .AND. (.Not. PRESENT(PNum))) CYCLE
ZoneNum = People(PeopleNum)%ZonePtr
IF (IsZoneDV(ZoneNum) .or. IsZoneUI(ZoneNum)) THEN
AirTemp = TCMF(ZoneNum) !PH 3/7/04
! UCSD-CV
ELSEIF (IsZoneCV(ZoneNum)) THEN
IF (ZoneUCSDCV(ZoneNum)%VforComfort == VComfort_Jet) THEN
AirTemp = ZTJET(ZoneNum)
ELSEIF (ZoneUCSDCV(ZoneNum)%VforComfort== VComfort_Recirculation) THEN
AirTemp = ZTJET(ZoneNum)
ELSE
! Thermal comfort control uses Tset to determine PMV setpoint value, otherwise use zone temp
If (PRESENT(PNum)) then
AirTemp = Tset
Else
AirTemp = ZTAV(ZoneNum)
End If
ENDIF
ELSE
If (PRESENT(PNum)) then
AirTemp = Tset
Else
AirTemp = ZTAVComf(ZoneNum)
End If
ENDIF
RadTemp = CalcRadTemp(PeopleNum)
! Use mean air temp for calculating RH when thermal comfort control is used
If (PRESENT(PNum)) then
RelHum = PsyRhFnTdbWPb(MAT(ZoneNum),ZoneAirHumRat(ZoneNum),OutBaroPress)
Else
RelHum = PsyRhFnTdbWPb(ZTAVComf(ZoneNum),ZoneAirHumRatAvgComf(ZoneNum),OutBaroPress)
End If
People(PeopleNum)%TemperatureInZone = AirTemp
People(PeopleNum)%RelativeHumidityInZone = RelHum * 100.0d0
! Metabolic rate of body (W/m2)
ActLevel = GetCurrentScheduleValue(People(PeopleNum)%ActivityLevelPtr)/BodySurfArea
! Energy consumption by external work (W/m2)
WorkEff = GetCurrentScheduleValue(People(PeopleNum)%WorkEffPtr)*ActLevel
! Clothing unit
SELECT CASE (People(PeopleNum)%ClothingType)
CASE (1)
CloUnit = GetCurrentScheduleValue(People(PeopleNum)%ClothingPtr)
CASE (2)
ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = (RadTemp+AirTemp)/2.0d0
ThermalComfortData(PeopleNum)%ClothingValue = CloUnit
CALL DynamicClothingModel
CloUnit = ThermalComfortData(PeopleNum)%ClothingValue
CASE (3)
IntermediateClothing = GetCurrentScheduleValue(People(PeopleNum)%ClothingMethodPtr)
IF(IntermediateClothing .EQ. 1.0d0) THEN
CloUnit = GetCurrentScheduleValue(People(PeopleNum)%ClothingPtr)
ThermalComfortData(PeopleNum)%ClothingValue = CloUnit
ELSE IF(IntermediateClothing .EQ. 2.0d0) THEN
ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = (RadTemp+AirTemp)/2.0d0
ThermalComfortData(PeopleNum)%ClothingValue = CloUnit
CALL DynamicClothingModel
CloUnit = ThermalComfortData(PeopleNum)%ClothingValue
ELSE
CloUnit = GetCurrentScheduleValue(People(PeopleNum)%ClothingPtr)
CALL ShowWarningError('PEOPLE="'//TRIM(People(PeopleNum)%Name)// &
'", Scheduled clothing value will be used rather than clothing calculation method.')
ENDIF
CASE DEFAULT
CALL ShowSevereError('PEOPLE="'//TRIM(People(PeopleNum)%Name)// &
'", Incorrect Clothing Type')
END SELECT
IF (IsZoneCV(ZoneNum)) THEN
IF (ZoneUCSDCV(ZoneNum)%VforComfort == VComfort_Jet) THEN
AirVel = Ujet(ZoneNum)
ELSEIF (ZoneUCSDCV(ZoneNum)%VforComfort== VComfort_Recirculation) THEN
AirVel = Urec(ZoneNum)
ELSE
AirVel = 0.2d0
ENDIF
ELSE
AirVel = GetCurrentScheduleValue(People(PeopleNum)%AirVelocityPtr)
! Ensure air velocity within the reasonable range. Otherwise reccusive warnings is provided
If (PRESENT(PNum) .AND. (AirVel < 0.1d0 .OR. AirVel > 0.5d0)) then
if (People(PeopleNum)%AirVelErrIndex == 0) then
CALL ShowWarningMessage('PEOPLE="'//TRIM(People(PeopleNum)%Name)// &
'", Air velocity is beyond the reasonable range (0.1,0.5) for thermal comfort control.')
CALL ShowContinueErrorTimeStamp(' ')
end if
CALL ShowRecurringWarningErrorAtEnd('PEOPLE="'//TRIM(People(PeopleNum)%Name)// &
'",Air velocity is still beyond the reasonable range (0.1,0.5)', &
People(PeopleNum)%AirVelErrIndex, ReportMinOf=AirVel,ReportMinUnits='[m/s]', &
ReportMaxOf=AirVel,ReportMaxUnits='[m/s]')
End If
ENDIF
! VapPress = CalcSatVapPressFromTemp(AirTemp) !original
! VapPress = RelHum*VapPress !original might be in torrs
VapPress = PsyPsatFnTemp(AirTemp) ! use psych routines inside E+ , returns Pa
VapPress = RelHum*VapPress ! in units of [Pa]
IntHeatProd = ActLevel - WorkEff
! Compute the Corresponding Clothed Body Ratio
CloBodyRat = 1.05d0 + 0.1d0*CloUnit ! The ratio of the surface area of the clothed body
! to the surface area of nude body
IF(CloUnit < 0.5d0) CloBodyRat = CloBodyRat - 0.05d0 + 0.1d0*CloUnit
AbsRadTemp = RadTemp + TAbsConv
AbsAirTemp = AirTemp + TAbsConv
CloInsul = CloUnit*CloBodyRat*0.155d0 ! Thermal resistance of the clothing
P2 = CloInsul*3.96d0
P3 = CloInsul*100.d0
P1 = CloInsul*AbsAirTemp
P4 = 308.7d0 - 0.028d0*IntHeatProd + P2*(AbsRadTemp/100.d0)**4
! First guess for clothed surface tempeature
AbsCloSurfTemp = AbsAirTemp + (35.5d0-AirTemp)/(3.5d0*(CloUnit + 0.1d0))
XN = AbsCloSurfTemp/100.d0
HcFor = 12.1d0*SQRT(AirVel) ! Heat transfer coefficient by forced convection
IterNum = 0
XF = XN
! COMPUTE SURFACE TEMPERATURE OF CLOTHING BY ITERATIONS
DO WHILE (( (ABS(XN - XF) > StopIterCrit) .OR. (IterNum == 0) ) &
.AND. (IterNum < MaxIter))
XF = (XF + XN)/2.d0
HcNat = 2.38d0*ABS(100.*XF - AbsAirTemp)**0.25d0 ! Heat transfer coefficient by natural convection
Hc = MAX(HcFor, HcNat) ! Determination of convective heat transfer coefficient
XN = (P4+P1*Hc - P2*XF**4)/(100.d0 + P3*Hc)
IterNum = IterNum + 1
IF (IterNum > MaxIter) THEN
CALL ShowWarningError('Max iteration exceeded in CalcThermalFanger')
END IF
END DO
AbsCloSurfTemp = 100.d0*XN
CloSurfTemp = AbsCloSurfTemp - TAbsConv
! COMPUTE PREDICTED MEAN VOTE
! Sensible heat loss
! RadHeatLoss = RadSurfEff*CloBodyRat*SkinEmiss*StefanBoltz* & !original
! (AbsCloSurfTemp**4 - AbsRadTemp**4) ! Heat loss by radiation
! following line is ln 480 in ASHRAE 55 append. D
RadHeatLoss = 3.96d0*CloBodyRat*((AbsCloSurfTemp/100.d0)**4.0d0 - (AbsRadTemp/100.d0)**4.0d0)
ConvHeatLoss = CloBodyRat*Hc*(CloSurfTemp - AirTemp) ! Heat loss by convection
DryHeatLoss = RadHeatLoss + ConvHeatLoss
! Evaporative heat loss
! Heat loss by regulatory sweating
EvapHeatLossRegComf = 0.0d0
IF (IntHeatProd > 58.2d0) THEN
EvapHeatLossRegComf = 0.42d0*(IntHeatProd - ActLevelConv)
END IF
! SkinTempComf = 35.7 - 0.028*IntHeatProd ! Skin temperature required to achieve thermal comfort
! SatSkinVapPress = 1.92*SkinTempComf - 25.3 ! Water vapor pressure at required skin temperature
! Heat loss by diffusion
! EvapHeatLossDiff = 0.4148*(SatSkinVapPress - VapPress) !original
EvapHeatLossDiff = 3.05d0 *0.001d0*(5733.d0 -6.99d0*IntHeatProd-VapPress) ! ln 440 in ASHRAE 55 Append. D
EvapHeatLoss = EvapHeatLossRegComf + EvapHeatLossDiff
! Heat loss by respiration
! original: LatRespHeatLoss = 0.0023*ActLevel*(44. - VapPress) ! Heat loss by latent respiration
LatRespHeatLoss = 1.7d0 * 0.00001d0 * ActLevel * (5867.d0 - VapPress) !ln 460 in ASHRAE 55 Append. D
! LatRespHeatLoss = 0.017251*ActLevel*(5.8662 - VapPress)
! V-1.2.2 'fix' BG 3/2005 5th term in LHS Eq (58) in 2001 HOF Ch. 8
! this was wrong because VapPress needed to be kPa
DryRespHeatLoss = 0.0014d0*ActLevel*(34.d0- AirTemp) ! Heat loss by dry respiration.
RespHeatLoss = LatRespHeatLoss + DryRespHeatLoss
ThermSensTransCoef = 0.303d0*EXP(-0.036d0*ActLevel) + 0.028d0 ! Thermal transfer coefficient to calculate PMV
PMV = ThermSensTransCoef*(IntHeatProd - EvapHeatLoss - RespHeatLoss - DryHeatLoss)
ThermalComfortData(PeopleNum)%FangerPMV = PMV
! Pass resulting PMV based on temperature setpoint (Tset) when using thermal comfort control
If (PRESENT(PNum)) then
PMVResult = PMV
End If
ThermalComfortData(PeopleNum)%ThermalComfortMRT = RadTemp
ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = (RadTemp+AirTemp)/2.0d0
ThermalComfortData(PeopleNum)%CloSurfTemp = CloSurfTemp
! Calculate the Fanger PPD (Predicted Percentage of Dissatisfied), as a %
PPD = 100.0d0 - 95.0d0*EXP(-0.03353d0*PMV**4 - 0.2179d0*PMV**2)
IF (PPD < 0.0d0 ) PPD = 0.0d0
IF (PPD > 100.0d0 ) PPD = 100.0d0
ThermalComfortData(PeopleNum)%FangerPPD = PPD
END DO
RETURN
END SUBROUTINE CalcThermalComfortFanger