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 CalcThermalComfortPierce
! SUBROUTINE INFORMATION:
! AUTHOR Jaewook Lee
! DATE WRITTEN January 2000
! MODIFIED Rick Strand (for E+ implementation February 2000)
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine calculates PMVET, PMVSET, DISC, and TSENS using the Pierce
! 2 Node model.
! 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 Pierce
! development. See documentation for further details and references.
! REFERENCES:
! Maloney, Dan, M.S. Thesis, University of Illinois at Urbana-Champaign
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: CloFac = 0.25d0 ! Clothing factor determined experimentally
REAL(r64), PARAMETER :: EvapEff = 0.9d0 ! Evaporative efficiency
REAL(r64), PARAMETER :: MaxSkinBloodFlow = 90.d0 ! Max. value of skin blood flow
REAL(r64), PARAMETER :: RegSweatMax = 670.d0 ! Max. value of regulatory sweating; w/m2
REAL(r64), PARAMETER :: SkinBloodFlowConst = 200.d0 ! Skin blood flow coefficient for average person; l/m2.hr.k
REAL(r64), PARAMETER :: STdAtm = 1.d0 ! Standard Atmospheres
REAL(r64), PARAMETER :: Str = 0.1d0 ! Constriction constant of skin blood flow for average person
REAL(r64), PARAMETER :: SweatContConst = 170.d0 ! Proportionality constant for sweat control; g/m2.hr
REAL(r64), PARAMETER :: VapPressConv = 0.1333227d0 ! Vapor pressure converter from torr to Kpa
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: AirEvapHeatResist ! Evaporative heat resistance of air
REAL(r64) :: ActMet ! Metalbolic rate in MET
REAL(r64) :: ActLevelStart ! Activity level at the start of the minute-by-minute iterations
REAL(r64) :: AvgBodyTemp ! Average body temperature
REAL(r64) :: AvgBodyTempHigh ! Average body temperature when HSI(Belding's classic heat sterss index) is 100
REAL(r64) :: AvgBodyTempLow ! Average body temperature when DISC is 0
REAL(r64) :: AvgBodyTempSet ! Setpoint for average body temperature
REAL(r64) :: BodyThermSigCold ! Temperature difference of Body when BodyTempSet is higher than BodyTemp
REAL(r64) :: BodyTempChange ! Temperature change of body in 1 minute
REAL(r64) :: BodyThermSigWarm ! Temperature difference of Body when BodyTemp is higher than BodyTempSet
REAL(r64) :: CloCond ! The conductance of the clothing
REAL(r64) :: CloEvapHeatResist ! Evaporative heat resistance of clothing
REAL(r64) :: CloSurfTempOld ! Old value of clothing surface temperature
REAL(r64) :: CoreThermSigCold ! Temperature difference of core when CoreTempSet is higher than CoreTemp
REAL(r64) :: CoreHeatStorage ! Heat storage in core compartment
REAL(r64) :: CoreTempSet ! Setpoint for body core temperature
REAL(r64) :: CoreThermSigWarm ! Temperature difference of core when CoreTemp is higher than CoreTempSet
REAL(r64) :: DryHeatLossET ! Heat loss from clothing surface due to both convection and radiation at ET
REAL(r64) :: DryHeatLossSET ! Heat loss from clothing surface due to both convection and radiation at SET
REAL(r64) :: EffectCloThermEff ! Effective clothing thermal efficiency
REAL(r64) :: EffectCloUnit ! Effective clothing unit; clo
REAL(r64) :: EnergyBalErrET ! Stop criterion for iteration to solve energy balance
REAL(r64) :: EnergyBalErrSET ! Stop criterion for iteration to solve energy balance
REAL(r64) :: ET ! Effective temperature
REAL(r64) :: EvapHeatLossStart ! Starting value of evaporative heat loss
LOGICAL :: FirstMinIter
REAL(r64) :: HcAct ! Convective heat transfer coefficient at high activity
REAL(r64) :: HcStd ! Standard convective heat transfer coefficient
REAL(r64) :: HrStd ! Standard radiant heat transfer coefficient
REAL(r64) :: HStd ! Standard combined heat transfer coefficient
INTEGER :: IterMin ! Time period for the ieterative calculation
REAL(r64) :: LewisRat ! Lewis ratio
REAL(r64) :: RegSweat ! The rate of regulatory sweating
REAL(r64) :: SET ! Standard effective temperature
REAL(r64) :: SkinBloodFlow ! The skin blood flow
REAL(r64) :: SkinThermSigCold ! Temperature difference of skin when SkinTempSet is higher than SkinTemp
REAL(r64) :: SkinHeatLoss ! Heat loss from skin
REAL(r64) :: SkinHeatStorage ! Heat storage in skin compartment
REAL(r64) :: SkinMassRat ! Actual skin mass to total body mass ratio
REAL(r64) :: SkinMassRatSet ! Setpoint for skin mass to total body mass ratio
REAL(r64) :: SkinRelHum ! Relative humidity at skin
REAL(r64) :: SkinTempSet ! Setpoint for skin temperature
REAL(r64) :: SkinThermSigWarm ! Temperature difference of skin when SkinTemp is higher than SkinTempSet
REAL(r64) :: StdCloBodyRat ! Standard ratio of clothed body
REAL(r64) :: StdCloFac ! Clothing factor determined experimentally at standard environment
REAL(r64) :: StdCloPermeatEff ! Standard clothing permeation efficiency
REAL(r64) :: StdCloUnit ! standard clothing unit
REAL(r64) :: StdEffectCloThermEff ! Standard effective clothing theraml efficiency
REAL(r64) :: StdEffectCloUnit ! standard effective clothing unit
REAL(r64) :: StdVapPressET ! Standard vapor pressure at effective temperature
REAL(r64) :: StdVapPressSET ! Standard vapor pressure at standar effective temperature
REAL(r64) :: TotEvapHeatResist ! Total evaporative heat resistance
REAL(r64) :: UnevapSweat ! Unevaporated sweat; g/m2/hr
REAL(r64) :: IntermediateClothing
! FLOW:
DO PeopleNum = 1, TotPeople
IF(.NOT. People(PeopleNum)%Pierce) CYCLE
ZoneNum = People(PeopleNum)%ZonePtr
IF (IsZoneDV(ZoneNum) .or. IsZoneUI(ZoneNum)) THEN
AirTemp = TCMF(ZoneNum) !PH 3/7/04
ELSE
AirTemp = ZTAV(ZoneNum)
ENDIF
RadTemp = CalcRadTemp(PeopleNum)
RelHum = PsyRhFnTdbWPb(ZTAV(ZoneNum),ZoneAirHumRat(ZoneNum),OutBaroPress)
! 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('Scheduled clothing value will be used rather than clothing calculation method.')
ENDIF
CASE DEFAULT
CALL ShowSevereError('Incorrect Clothing Type')
END SELECT
AirVel = GetCurrentScheduleValue(People(PeopleNum)%AirVelocityPtr)
VapPress = CalcSatVapPressFromTemp(AirTemp)
VapPress = RelHum*VapPress
VapPress = VapPress*VapPressConv ! Torr to KPa (5.8662 kPa=44 mmHg; .017251=.0023*760 mmHg/101.325 kPa)
IntHeatProd = ActLevel - WorkEff
ActMet = ActLevel/ActLevelConv
! CALCULATE VARIABLESS THAT REMAIN CONSTANT FOR AN HOUR
CloBodyRat = 1.0d0 + CloFac*CloUnit
IF(CloUnit < .01d0) CloUnit=.01d0
CloCond = 1.d0/(CloUnit*0.155d0)
! INITIALIZE THE POLLOWING VARIABLES
IF(AirVel < .137d0) AirVel = .137d0
Hc = 8.6d0*AirVel**0.53d0
IF(ActMet > .9d0) THEN
HcAct = 5.66d0*(ActMet - 0.85d0)**0.39d0
Hc = MAX(HcAct, Hc)
ENDIF
! Definition of vascular control signals
! CoreTempSet, SkinTempSet, and AvgBodyTempSet are the setpoints for core, skin and
! average body temperatures corresponding to physiol. neutrality
! SkinMassRatSet is the ratio of skin mass to total body mass (skin+core)
! Typical values for CoreTempSet, SkinTempSet and SkinMassRatSet are 36.8, 33.7 and 0.10
! SkinMassRat is the actual skin to total body mass ratio
SkinTempSet = 33.7d0
CoreTempSet = 36.8d0
SkinMassRatSet = 0.10d0
AvgBodyTempSet = SkinMassRatSet*SkinTempSet + (1.d0-SkinMassRatSet)*CoreTempSet
! APPROXIMATE THE FOLLOWING VALUES TO START
SkinTemp = 33.7d0
CoreTemp = 36.8d0
SkinBloodFlow = 6.3d0
EvapHeatLossStart = 5.0d0
LatRespHeatLoss = 0.017251d0*ActLevel*(5.8662d0 - VapPress)
EvapHeatLoss = (EvapHeatLossStart - LatRespHeatLoss)
SkinMassRat = 0.0417737d0 + 0.7451832d0/(SkinBloodFlow + 0.585417d0)
! GUESS CloSurfTemp TO START
CloSurfTemp = (SkinTemp + AirTemp)/2.d0
! SIMULATION OF TEMPERATURE REGULATION.
! This SECTION simulates the temperature regulation over 1 minute.
! Inputs are the physiological data from the previous time step and
! the current environmental conditions.
! BEGIN MINUTE BY MINUTE CALCULATIONS FOR ONE HOUR
ActLevelStart = ActLevel ! ActLevel gets increased by shivering in the following DO
! loop and must be increased from the start level, not
! perpetually increased
DO IterMin = 1, 60
! Dry heat balance: solve for CloSurfTemp and Hr
FirstMinIter = .TRUE.
CloSurfTempOld=0.0d0
DO WHILE ((ABS(CloSurfTemp-CloSurfTempOld) > 0.01d0) .OR. FirstMinIter)
FirstMinIter = .FALSE.
CloSurfTempOld = CloSurfTemp
Hr = 4.d0*RadSurfEff*StefanBoltz*((CloSurfTemp + RadTemp)/2.d0 + TAbsConv)**3
CloSurfTemp = (CloCond*SkinTemp + CloBodyRat*(Hc*AirTemp + Hr*RadTemp))/(CloCond + CloBodyRat*(Hc + Hr))
END DO
! CALCULATE THE COMBINED HEAT TRANSFER COEFF. (H)
H = Hr+Hc
! Heat flow from Clothing surface to environment
DryHeatLoss = CloBodyRat*(Hc*(CloSurfTemp - AirTemp) + Hr*(CloSurfTemp - RadTemp))
! dry and latent respiratory heat losses
LatRespHeatLoss = 0.017251d0*ActLevel*(5.8662d0 - VapPress)
DryRespHeatLoss = 0.0014d0*ActLevel*(34.d0 - AirTemp)*StdAtm
RespHeatLoss = LatRespHeatLoss + DryRespHeatLoss
! Heat flows to skin and core:
HeatFlow = (CoreTemp-SkinTemp)*(5.28d0 + 1.163d0*SkinBloodFlow)
! 5.28 is skin conductance in the
! absence of skin blood flow
SkinHeatStorage = HeatFlow - DryHeatLoss - EvapHeatLoss
CoreHeatStorage = ActLevel - (CoreTemp - SkinTemp)*(5.28d0+1.163d0*SkinBloodFlow) - &
RespHeatLoss - WorkEff
! Thermal capacities (average man: 70 kg, 1.8 square meter).
CoreThermCap = ActLevelConv*(1.d0 - SkinMassRat)*70.d0
SkinThermCap = ActLevelConv*SkinMassRat*70.d0
! Temperature changes in 1 minute
SkinTempChange = (SkinHeatStorage*1.8d0)/SkinThermCap
CoreTempChange = (CoreHeatStorage*1.8d0)/CoreThermCap
BodyTempChange = SkinMassRat*SkinTempChange + (1.d0 - SkinMassRat)*CoreTempChange
SkinTemp = SkinTemp + SkinTempChange
CoreTemp = CoreTemp + CoreTempChange
AvgBodyTemp = SkinMassRat*SkinTemp + (1.d0 - SkinMassRat)*CoreTemp
IF(SkinTemp > SkinTempSet) THEN
SkinThermSigWarm = SkinTemp - SkinTempSet
SkinThermSigCold = 0.d0
ELSE
SkinThermSigCold = SkinTempSet - SkinTemp
SkinThermSigWarm = 0.d0
END IF
IF(CoreTemp > CoreTempSet) THEN
CoreThermSigWarm = CoreTemp - CoreTempSet
CoreThermSigCold = 0.d0
ELSE
CoreThermSigCold = CoreTempSet - CoreTemp
CoreThermSigWarm = 0.d0
END IF
IF(AvgBodyTemp > AvgBodyTempSet) THEN
BodyThermSigWarm = AvgBodyTemp - AvgBodyTempSet
BodyThermSigCold = 0.d0
ELSE
BodyThermSigCold = AvgBodyTempSet-AvgBodyTemp
BodyThermSigWarm = 0.d0
END IF
VasodilationFac = SkinBloodFlowConst*CoreThermSigWarm
VasoconstrictFac = Str*SkinThermSigCold
SkinBloodFlow = (6.3d0 + VasodilationFac)/(1.d0 + VasoconstrictFac)
! SkinBloodFlow is never below 0.5 liter/(m2.hr) nor above MaxSkinBloodFlow
IF(SkinBloodFlow < 0.5d0) SkinBloodFlow = 0.5d0
IF(SkinBloodFlow > MaxSkinBloodFlow) SkinBloodFlow = MaxSkinBloodFlow
! ratio of skin-core masses change with SkinBloodFlow
! (SkinMassRat,SkinBloodFlow) = (.15,6.3),(.45,1.24),(.05,90)
SkinMassRat = 0.0417737d0 + 0.7451832d0/(SkinBloodFlow + 0.585417d0)
! control of regulatory sweating
RegSweat = SweatContConst*BodyThermSigWarm*EXP(SkinThermSigWarm/10.7d0)
IF(RegSweat > RegSweatMax) RegSweat = RegSweatMax
EvapHeatLossRegSweat = 0.68d0*RegSweat
! adjustment of metabolic heat due to shivering (Stolwijk, Hardy)
ShivResponse = 19.4d0*SkinThermSigCold*CoreThermSigCold
ActLevel = ActLevelStart + ShivResponse
! Evaluation of heat transfer by evaporation at skin surface
! LewisRat varies with SkinTemp.
! LewisRat=2.02 C/mmHg or 15.1512 C/kPa at 0 C (lr=2.2 at 25 C)
LewisRat = 15.1512d0*(SkinTemp + TAbsConv)/TAbsConv
! Mass transfer equation between skin and environment
! TotEvapHeatResist is total vapor resistance of CloUnitthing + air layer
! CloInsul is efficiency of mass transfer for CloUnitthing
! CloInsul IS SET TO .45 (FOR WOVEN MATERIAL)
! Reference: Woodcock, Breckenridge and Goldman
CloInsul = 0.45d0
CloThermEff = 1.d0/(1.d0 + 0.155d0*CloBodyRat*H*CloUnit)
AirEvapHeatResist = 1.d0/(LewisRat*CloBodyRat*Hc)
CloEvapHeatResist = 0.155d0*CloUnit/(LewisRat*CloInsul)
TotEvapHeatResist = AirEvapHeatResist + CloEvapHeatResist
SatSkinVapPress = CalcSatVapPressFromTemp(SkinTemp)
SatSkinVapPress = SatSkinVapPress*0.1333227d0
EvapHeatLossMax = (1.d0/TotEvapHeatResist)*(SatSkinVapPress - VapPress)
SkinWetSweat = EvapHeatLossRegSweat/EvapHeatLossMax
! 0.06 if SkinWetDiff for nonsweating skin --- Kerslake
SkinWetDiff = (1.d0-SkinWetSweat)*.06d0
EvapHeatLossDiff = SkinWetDiff*EvapHeatLossMax
EvapHeatLoss = EvapHeatLossRegSweat + EvapHeatLossDiff
SkinWetTot = EvapHeatLoss/EvapHeatLossMax
! Beginning of dripping (Sweat not evaporated on skin surface)
IF((SkinWetTot >= EvapEff).AND.(EvapHeatLossMax >= 0)) THEN
SkinWetTot = EvapEff
SkinWetSweat = (EvapEff - 0.06d0)/.94d0
EvapHeatLossRegSweat = SkinWetSweat*EvapHeatLossMax
SkinWetDiff = (1.d0 - SkinWetSweat)*.06d0
EvapHeatLossDiff = SkinWetDiff*EvapHeatLossMax
EvapHeatLoss = EvapHeatLossRegSweat + EvapHeatLossDiff
END IF
! When EvapHeatLossMax<0. condensation on skin occurs.
IF(EvapHeatLossMax <= 0.0d0) THEN
SkinWetDiff = 0.0d0
EvapHeatLossDiff = 0.0d0
EvapHeatLoss = EvapHeatLossMax
SkinWetTot = EvapEff
SkinWetSweat = EvapEff
EvapHeatLossRegSweat = 0.0d0
END IF
! UnevapSweat = unevaporated sweat in grams/sq.m/hr
UnevapSweat = (RegSweat*.68d0 - SkinWetSweat*EvapHeatLossMax)/0.68d0
IF(UnevapSweat <= 0.0d0) UnevapSweat=0.0d0
! Vapor pressure at skin (as measured by dewpoint sensors)
SkinVapPress=SkinWetTot*SatSkinVapPress + (1.d0 - SkinWetTot)*VapPress
! SkinRelHum is skin relative humidity
SkinRelHum = SkinVapPress/SatSkinVapPress
END DO ! END OF MINUTE BY MINUTE TEMPERATURE REGULATION LOOP
! Computation of comfort indices.
! Inputs to this SECTION are the physiological data from the simulation of
! temperature regulation loop
! PART I: Heat transfer indices in real environment
OpTemp = (Hr*RadTemp + Hc*AirTemp)/H
EffectCloUnit = CloUnit - (CloBodyRat-1.d0)/(.155d0*CloBodyRat*H)
EffectCloThermEff = 1.d0/(1.d0 + .155d0*H*EffectCloUnit)
CloPermeatEff = 1.d0/(1.d0 + (.155d0/CloInsul)*Hc*EffectCloUnit)
! PART II: ET*(standardization humidity/REAL(r64) CloUnit, StdAtm and Hc)
! calculation of skin heat Loss (SkinHeatLoss)
SkinHeatLoss = H*EffectCloThermEff*(SkinTemp - OpTemp) + &
SkinWetTot*LewisRat*Hc*CloPermeatEff*(SatSkinVapPress - VapPress)
! Get a low approximation for ET* and solve balance
! equation by iteration
ET = SkinTemp - SkinHeatLoss/(H*EffectCloThermEff)
! THE STANDARD VAPOR PRESSURE AT THE EFFECTIVE TEMP : StdVapPressET
DO
StdVapPressET = CalcSatVapPressFromTemp(ET)
StdVapPressET = StdVapPressET*VapPressConv
EnergyBalErrET = SkinHeatLoss - H*EffectCloThermEff*(SkinTemp - ET) - &
SkinWetTot*LewisRat*Hc*CloPermeatEff*(SatSkinVapPress - StdVapPressET/2.0d0)
IF (EnergyBalErrET >= 0.0d0) EXIT
ET = ET + 0.1d0
END DO
! Part III: Standard effective temperature SET*
! standardized humidity. Hc, CloUnit, StdAtm
! normalized for given ActLeAirVelivity
! Standard environment
HrStd = Hr
! HcStd = standard conv. heat tr. coeff. (level walking/still air)
IF(ActMet <= 0.86d0) ActMet = 0.86d0
HcStd = 5.66d0*(ActMet - 0.85d0)**0.39d0
! minimum value of Hc at sea leAirVel = 3.0 (AirVel = .137 m/s)
IF(HcStd <= 3.d0) HcStd = 3.d0
! standard MET - StdCloUnit relation gives SET* = 24 C when PMV = 0
StdCloUnit = 1.3264d0/((ActLevel-WorkEff)/ActLevelConv + 0.7383d0) - 0.0953d0
StdCloFac = CloFac
StdCloBodyRat = 1.d0 + StdCloFac*StdCloUnit
HStd = HrStd + HcStd
StdEffectCloUnit = StdCloUnit - (StdCloBodyRat - 1.d0)/(0.155d0*StdCloBodyRat*HStd)
StdEffectCloThermEff = 1.d0/(1.d0 + 0.155d0*HStd*StdEffectCloUnit)
StdCloPermeatEff = 1.d0/(1.d0+(0.155d0/.45d0)*HcStd*StdEffectCloUnit)
! Get a low approximation for SET*
! and solve balance equ. by iteration
SET = SkinTemp - SkinHeatLoss/(HStd*StdEffectCloThermEff)
DO
StdVapPressSET = CalcSatVapPressFromTemp(SET)
StdVapPressSET = StdVapPressSET*VapPressConv
EnergyBalErrSET = SkinHeatLoss - HStd*StdEffectCloThermEff*(SkinTemp - SET) - &
SkinWetTot*LewisRat*HcStd*StdCloPermeatEff*(SatSkinVapPress - StdVapPressSET/2.0d0)
IF (EnergyBalErrSET >= 0.0d0) EXIT
SET = SET + 0.1d0
END DO
! Part IV: Fanger's comfort equation.
! Thermal transfer coefficient to calculate PMV
ThermSensTransCoef = 0.303d0*EXP(-0.036d0*ActLevel) + 0.028d0
! Fanger's reg. sweating at comfort threshold (PMV=0) is:
EvapHeatLossRegComf = (IntHeatProd - ActLevelConv)*0.42d0
! PMV*(PMVET in prgm) uses ET instead of OpTemp
DryHeatLossET = HStd*StdEffectCloThermEff*(SkinTemp - ET)
ThermalComfortData(PeopleNum)%PiercePMVET = ThermSensTransCoef*(IntHeatProd - RespHeatLoss - &
DryHeatLossET - EvapHeatLossDiff - EvapHeatLossRegComf)
! SPMV*(PMVSET in prgm) uses SET instead of OpTemp
DryHeatLossSET = HStd*StdEffectCloThermEff*(SkinTemp - SET)
ThermalComfortData(PeopleNum)%PiercePMVSET = ThermSensTransCoef*(IntHeatProd - RespHeatLoss - &
DryHeatLossSET - EvapHeatLossDiff - EvapHeatLossRegComf)
! Part V: Heat stress and heat strain indices derived from EvapHeatLoss,
! EvapHeatLossMax and W (skin wettedness)
! EvapHeatLossMax is readjusted for EvapEff
EvapHeatLossMax = EvapHeatLossMax*EvapEff
! DISC (discomfort) varies with relative thermoregulatory strain
ThermalComfortData(PeopleNum)%PierceDISC = 5.d0*(EvapHeatLossRegSweat - EvapHeatLossRegComf)/(EvapHeatLossMax - &
EvapHeatLossRegComf - EvapHeatLossDiff)
! Part VI: Thermal sensation TSENS as function of mean body temp.-
! AvgBodyTempLow is AvgBodyTemp when DISC is 0. (lower limit of zone of evap. regul.)
AvgBodyTempLow = (0.185d0/ActLevelConv)*(ActLevel - WorkEff) + 36.313d0
! AvgBodyTempHigh is AvgBodyTemp when HSI=100 (upper limit of zone of evap. regul.)
AvgBodyTempHigh = (0.359d0/ActLevelConv)*(ActLevel - WorkEff) + 36.664d0
! TSENS=DISC=4.7 when HSI =1 00 (HSI is Belding's classic heat stress index)
! In cold, DISC &TSENS are the same and neg. fct of AvgBodyTemp
IF(AvgBodyTemp > AvgBodyTempLow) THEN
ThermalComfortData(PeopleNum)%PierceTSENS = 4.7d0*(AvgBodyTemp - AvgBodyTempLow)/(AvgBodyTempHigh - &
AvgBodyTempLow)
ELSE
ThermalComfortData(PeopleNum)%PierceTSENS = .68175d0*(AvgBodyTemp - AvgBodyTempLow)
ThermalComfortData(PeopleNum)%PierceDISC = ThermalComfortData(PeopleNum)%PierceTSENS
END IF
ThermalComfortData(PeopleNum)%ThermalComfortMRT = RadTemp
ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = (RadTemp+AirTemp)/2.0d0
END DO
RETURN
END SUBROUTINE CalcThermalComfortPierce