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 CalcThermalComfortKSU
! 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 TSV using the KSU 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 :: CloEmiss = 0.8d0 ! Clothing Emissivity
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: BodyWt ! Weight of body, kg
REAL(r64), DIMENSION(2) :: Coeff ! Coefficients used in Range-Kutta's Method
REAL(r64) :: DayNum ! Number of days of acclimation
INTEGER :: NumDay ! Loop counter for DayNum
REAL(r64) :: EmissAvg ! Average emissivity
INTEGER :: IncreDayNum ! Number of days of increment in the outputs as desired
REAL(r64) :: IntHeatProdMet ! Internal heat production in MET
REAL(r64) :: IntHeatProdMetMax ! Maximum value of internal heat production in MET
INTEGER :: LastDayNum ! Number of days for the last print out
REAL(r64) :: SkinWetFac ! Skin wettedness factor
REAL(r64) :: SkinWetNeut ! Skin wettedness at neutral state
INTEGER :: StartDayNum ! Number of days for the first print out
! Unacclimated man = 1, Acclimated man = 14
REAL(r64) :: SweatSuppFac ! Sweat suppression factor due to skin wettedness
REAL(r64), DIMENSION(2) :: Temp ! Temperature
REAL(r64), DIMENSION(2) :: TempChange ! Change of temperature
REAL(r64) :: TempDiffer ! Temperature difference between the rectal and esophageal temperatures
! If not measured, set it to be 0.5 Deg. C.
INTEGER :: TempIndiceNum ! Number of temperature indices
REAL(r64) :: ThermCndctMin ! Minimum value of thermal conductance
REAL(r64) :: ThermCndctNeut ! Thermal conductance at neutral state
REAL(r64) :: TimeExpos ! Time period in the exposure, hr
REAL(r64) :: TimeInterval ! Time interval of outputs desired, hr
REAL(r64) :: TSVMax ! Maximum value of thermal sensation vote
REAL(r64) :: IntermediateClothing
! FLOW:
TempIndiceNum = 2
! NEXT GROUP OF VARIABLE ARE FIXED FOR BLAST PROGRAM - UNACCLIMATED MAN
! THE TSV MODEL CAN BE APPLIED TO UNACCLIMATED MAN ONLY.
TimeInterval = 1.d0
TSVMax = 4.d0
StartDayNum = 1
LastDayNum = 1
IncreDayNum = 1
TimeExpos = 1.d0
TempDiffer = 0.5d0
DO PeopleNum = 1, TotPeople
! THE NEXT SIX VARIABLES WILL BE READ IN FROM INPUT DECK
IF(.NOT. People(PeopleNum)%KSU) 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)
ActLevel = GetCurrentScheduleValue(People(PeopleNum)%ActivityLevelPtr)/BodySurfArea
WorkEff = GetCurrentScheduleValue(People(PeopleNum)%WorkEffPtr)*ActLevel
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
AirVel = GetCurrentScheduleValue(People(PeopleNum)%AirVelocityPtr)
IntHeatProd = ActLevel - WorkEff
! THE FOLLOWING ARE TYPICAL VALUES SET FOR BLAST RUNS
! STANDARD MAN: 70. KG WEIGHT, 1.8 M2 SURFACE AREA
BodyWt = 70.d0
CoreTemp = 37.d0
SkinTemp = 31.d0
! CALCULATIONS NEEDED FOR THE PASSIVE STATE EQUATIONS
CoreThermCap = 0.9d0*BodyWt*0.97d0/BodySurfArea
SkinThermCap = 0.1d0*BodyWt*0.97d0/BodySurfArea
! KERSLAKE'S FORMULA (0.05<AirVel<5. M/S)
IF(AirVel < 0.137d0) AirVel = 0.137d0
Hc = 8.3d0*SQRT(AirVel)
EmissAvg = RadSurfEff*CloEmiss + (1.d0 - RadSurfEff)*1.d0
! IBERALL EQUATION
Hr = EmissAvg*(3.87d0 + 0.031d0*RadTemp)
H = Hr+Hc
OpTemp = (Hc*AirTemp + Hr*RadTemp)/H
VapPress = CalcSatVapPressFromTemp(AirTemp)
VapPress = RelHum*VapPress
CloBodyRat = 1.0d0+0.2d0*CloUnit
CloThermEff = 1.d0/(1.d0 + 0.155d0*H*CloBodyRat*CloUnit)
CloPermeatEff = 1.d0/(1.d0 + 0.143d0*Hc*CloUnit)
! CALCULATE THE PHYSIOLOGICAL REACTIONS OF AN UNACCLIMATED
! MAN (LastDayNum = 1), OR AN ACCLIMATED MAN (LastDayNum = 14, IncreDayNum = 13),
DO NumDay = StartDayNum,LastDayNum,IncreDayNum
! INITIAL CONDITIONS IN AN EXPOSURE
DayNum=REAL(NumDay,r64)
Time = 0.0d0
TimeChange = .01d0
SweatSuppFac = 1.d0
Temp(1) = CoreTemp
Temp(2) = SkinTemp
Coeff(1) = 0.0d0
Coeff(2) = 0.0d0
! PHYSIOLOGICAL ADJUSTMENTS IN HEAT ACCLIMATION.
AcclPattern = 1.d0 - EXP(-0.12d0*(DayNum - 1.0d0))
CoreTempNeut = 36.9d0 - 0.6d0*AcclPattern
SkinTempNeut = 33.8d0 - 1.6d0*AcclPattern
ActLevel = ActLevel - 0.07d0*ActLevel*AcclPattern
! BASIC INFORMATION FOR THERMAL SENSATION.
IntHeatProdMet = IntHeatProd/ActLevelConv
IntHeatProdMetMax = MAX(1.d0,IntHeatProdMet)
ThermCndctNeut = 12.05d0*EXP(0.2266d0*(IntHeatProdMetMax - 1.0d0))
SkinWetNeut = 0.02d0 + 0.4d0*(1.d0-EXP(-0.6d0*(IntHeatProdMetMax - 1.0d0)))
ThermCndctMin = (ThermCndctNeut - 5.3d0)*0.26074074d0 + 5.3d0
! CALCULATION OF CoreTempChange/TempChange & SkinTempChange/TempChange
CALL DERIV(TempIndiceNum,Temp,TempChange)
DO
! CALCULATION OF THERMAL SENSATION VOTE (TSV).
! THE TSV MODEL CAN BE APPLIED TO UNACCLIMATED MAN ONLY.
SkinWetFac = (SkinWetSweat - SkinWetNeut)/(1.d0 - SkinWetNeut)
VasodilationFac = (ThermCndct - ThermCndctNeut)/(75.d0 - ThermCndctNeut)
VasoconstrictFac = (ThermCndctNeut - ThermCndct)/(ThermCndctNeut - ThermCndctMin)
! IF VasodilationFac < 0.0, VASOCONSTRICTION OCCURS AND RESULTS IN COLD SENSATION.
! OTHERWISE NORMAL BLOOD FLOW OR VASODILATION OCCURS AND RESULTS IN
! THERMAL NEUTRALITY OR WARM SENSATION.
IF (VasodilationFac < 0) THEN
ThermalComfortData(PeopleNum)%KsuTSV = -1.46153d0*VasoconstrictFac + 3.74721d0*VasoconstrictFac**2 - &
6.168856d0*VasoconstrictFac**3
ELSE
ThermalComfortData(PeopleNum)%KsuTSV = (5.d0 - 6.56d0*(RelHum - 0.50d0))*SkinWetFac
IF (ThermalComfortData(PeopleNum)%KsuTSV > TSVMax) ThermalComfortData(PeopleNum)%KsuTSV = TSVMax
END IF
ThermalComfortData(PeopleNum)%ThermalComfortMRT = RadTemp
ThermalComfortData(PeopleNum)%ThermalComfortOpTemp = (RadTemp+AirTemp)/2.0d0
CoreTemp = Temp(1)
SkinTemp = Temp(2)
EvapHeatLossSweatPrev = EvapHeatLossSweat
CALL RKG (TempIndiceNum,TimeChange,Time,Temp,TempChange,Coeff)
IF (Time > TimeExpos) EXIT
END DO
END DO
END DO
RETURN
END SUBROUTINE CalcThermalComfortKSU