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.
! Error trap for zones that do not exist or zones not in the zone the thermal chimney is in LKL-more renaming effort and code review might be possible here
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
logical, | intent(inout) | :: | ErrorsFound |
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 GetThermalChimney(ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Kwang Ho Lee
! DATE WRITTEN April 2008
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine obtains input data for ThermalChimney units and
! stores it in the ThermalChimney data structure.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE InputProcessor, ONLY: GetNumObjectsFound,GetObjectItem,FindItemInList,VerifyName
USE ScheduleManager, ONLY: GetScheduleIndex
USE General, ONLY: RoundSigDigits
USE DataIPShortCuts
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ErrorsFound ! If errors found in input
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: Blank=' '
REAL(r64), PARAMETER :: FlowFractionTolerance = 0.0001d0 ! Smallest deviation from unity for the sum of all fractions
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
! CHARACTER(len=MaxNameLength), DIMENSION(23) :: AlphaName
! REAL(r64) , DIMENSION(63) :: IHGNumbers
INTEGER :: NumAlpha
INTEGER :: NumNumber
REAL(r64) :: AllRatiosSummed !
INTEGER :: TCZoneNum ! Thermal chimney zone counter
INTEGER :: TCZoneNum1 ! Thermal chimney zone counter
INTEGER :: IOStat
INTEGER :: Loop
INTEGER :: Loop1
LOGICAL :: IsNotOK
LOGICAL :: IsBlank
! ALLOCATE(MCPTThermChim(NumOfZones))
! MCPTThermChim=0.0
! ALLOCATE(MCPThermChim(NumOfZones))
! MCPThermChim=0.0
! ALLOCATE(ThermChimAMFL(NumOfZones))
! ThermChimAMFL=0.0
! Following used for reporting
ALLOCATE (ZnRptThermChim (NumOfZones))
cCurrentModuleObject='ZoneThermalChimney'
TotThermalChimney=GetNumObjectsFound(cCurrentModuleObject)
ALLOCATE (ThermalChimneySys(TotThermalChimney))
ALLOCATE (ThermalChimneyReport(TotThermalChimney))
DO Loop=1, TotThermalChimney
CALL GetObjectItem(cCurrentModuleObject,Loop,cAlphaArgs,NumAlpha,rNumericArgs,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
! First Alpha is Thermal Chimney Name
IsNotOK=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),ThermalChimneySys%Name,Loop,IsNotOK,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (IsNotOK) THEN
ErrorsFound=.true.
IF (IsBlank) THEN
CYCLE
ELSE
cAlphaArgs(1)=TRIM(cAlphaArgs(1))//'--dup'
ENDIF
ENDIF
ThermalChimneySys(Loop)%Name = cAlphaArgs(1)
! Second Alpha is Zone Name
ThermalChimneySys(Loop)%RealZonePtr = FindIteminList(cAlphaArgs(2),Zone%Name,NumOfZones)
IF (ThermalChimneySys(Loop)%RealZonePtr == 0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid Zone')
CALL ShowContinueError('invalid - not found '//trim(cAlphaFieldNames(2))//'="'//trim(cAlphaArgs(2))//'".')
ErrorsFound = .TRUE.
ELSEIF (.not. Zone(ThermalChimneySys(Loop)%RealZonePtr)%HasWindow) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid Zone')
CALL ShowContinueError('...invalid - no window(s) in '//trim(cAlphaFieldNames(2))//'="'//trim(cAlphaArgs(2))//'".')
CALL ShowContinueError('...thermal chimney zones must have window(s).')
ErrorsFound = .TRUE.
ENDIF
ThermalChimneySys(Loop)%RealZoneName = cAlphaArgs(2)
ThermalChimneySys(Loop)%SchedName = cAlphaArgs(3)
IF (lAlphaFieldBlanks(3)) THEN
ThermalChimneySys(Loop)%SchedPtr = ScheduleAlwaysOn
ELSE
ThermalChimneySys(Loop)%SchedPtr = GetScheduleIndex(cAlphaArgs(3))
IF (ThermalChimneySys(Loop)%SchedPtr == 0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid data')
CALL ShowContinueError('Invalid-not found '//trim(cAlphaFieldNames(3))//'="'//trim(cAlphaArgs(3))//'".')
ErrorsFound = .TRUE.
END IF
END IF
ThermalChimneySys(Loop)%AbsorberWallWidth = rNumericArgs(1)
IF (ThermalChimneySys(Loop)%AbsorberWallWidth < 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cNumericFieldNames(1))//' must be >= 0, entered value=['//trim(RoundSigDigits(rNumericArgs(1),2))//'].')
ErrorsFound = .TRUE.
END IF
ThermalChimneySys(Loop)%AirOutletCrossArea = rNumericArgs(2)
IF (ThermalChimneySys(Loop)%AirOutletCrossArea < 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cNumericFieldNames(2))//' must be >= 0, entered value=['//trim(RoundSigDigits(rNumericArgs(2),2))//'].')
ErrorsFound = .TRUE.
END IF
ThermalChimneySys(Loop)%DischargeCoeff = rNumericArgs(3)
IF ((ThermalChimneySys(Loop)%DischargeCoeff <= 0.0d0) .OR. &
(ThermalChimneySys(Loop)%DischargeCoeff > 1.0d0)) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cNumericFieldNames(3))//' must be > 0 and <=1.0, entered value=['//trim(RoundSigDigits(rNumericArgs(3),2))//'].')
ErrorsFound = .TRUE.
END IF
ThermalChimneySys(Loop)%TotZoneToDistrib = NumAlpha - 3
ALLOCATE(ThermalChimneySys(Loop)%ZonePtr(ThermalChimneySys(Loop)%TotZoneToDistrib))
ALLOCATE(ThermalChimneySys(Loop)%ZoneName(ThermalChimneySys(Loop)%TotZoneToDistrib))
ALLOCATE(ThermalChimneySys(Loop)%DistanceThermChimInlet(ThermalChimneySys(Loop)%TotZoneToDistrib))
ALLOCATE(ThermalChimneySys(Loop)%RatioThermChimAirFlow(ThermalChimneySys(Loop)%TotZoneToDistrib))
ALLOCATE(ThermalChimneySys(Loop)%EachAirInletCrossArea(ThermalChimneySys(Loop)%TotZoneToDistrib))
AllRatiosSummed = 0.0d0
DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
ThermalChimneySys(Loop)%ZoneName(TCZoneNum) = cAlphaArgs(TCZoneNum+3)
ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) = FindIteminList(cAlphaArgs(TCZoneNum+3),Zone%Name,NumOfZones)
ThermalChimneySys(Loop)%DistanceThermChimInlet(TCZoneNum) = rNumericArgs(3*TCZoneNum+1)
ThermalChimneySys(Loop)%RatioThermChimAirFlow(TCZoneNum) = rNumericArgs(3*TCZoneNum+2)
IF (lNumericFieldBlanks(3*TCZoneNum+2)) ThermalChimneySys(Loop)%RatioThermChimAirFlow(TCZoneNum) = 1.0d0
ThermalChimneySys(Loop)%EachAirInletCrossArea(TCZoneNum) = rNumericArgs(3*TCZoneNum+3)
!!! Error trap for zones that do not exist or zones not in the zone the thermal chimney is in
IF (ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == 0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cAlphaFieldNames(TCZoneNum+3))//'="'//trim(cAlphaArgs(TCZoneNum+3))//'" not found.')
ErrorsFound=.true.
ELSE IF (ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop)%RealZonePtr) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid reference '// &
trim(cAlphaFieldNames(2))//'="'//trim(cAlphaArgs(2)))
CALL ShowContinueError('...must not have same zone as reference= '// &
trim(cAlphaFieldNames(TCZoneNum+3))//'="'//trim(cAlphaArgs(TCZoneNum+3))//'".')
ErrorsFound=.true.
END IF
IF (ThermalChimneySys(Loop)%DistanceThermChimInlet(TCZoneNum) < 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cNumericFieldNames(3*TCZoneNum+1))//' must be >= 0, entered value=['// &
trim(RoundSigDigits(rNumericArgs(3*TCZoneNum+1),2))//'].')
ErrorsFound = .TRUE.
END IF
IF ((ThermalChimneySys(Loop)%RatioThermChimAirFlow(TCZoneNum) <= 0.0d0) .OR. &
(ThermalChimneySys(Loop)%RatioThermChimAirFlow(TCZoneNum) > 1.0d0)) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cNumericFieldNames(3*TCZoneNum+2))//' must be > 0 and <=1.0, entered value=['// &
trim(RoundSigDigits(rNumericArgs(3*TCZoneNum+2),2))//'].')
ErrorsFound = .TRUE.
END IF
IF (ThermalChimneySys(Loop)%EachAirInletCrossArea(TCZoneNum) < 0.0d0) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
trim(cNumericFieldNames(3*TCZoneNum+3))//' must be >= 0, entered value=['// &
trim(RoundSigDigits(rNumericArgs(3*TCZoneNum+3),2))//'].')
ErrorsFound = .TRUE.
END IF
AllRatiosSummed = AllRatiosSummed + ThermalChimneySys(Loop)%RatioThermChimAirFlow(TCZoneNum)
END DO ! DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
! Error trap if the sum of fractions is not equal to 1.0
IF (ABS(AllRatiosSummed-1.0d0) > FlowFractionTolerance) THEN
CALL ShowSevereError(trim(cCurrentModuleObject)//'="'//trim(cAlphaArgs(1))//' invalid '// &
'sum of fractions, must be =1.0, entered value (summed from entries)=['// &
trim(RoundSigDigits(AllRatiosSummed,4))//'].')
ErrorsFound = .TRUE.
END IF
END DO ! DO Loop=1, TotThermalChimney
! Set up the output variables for thermal chimneys
DO Loop=1, TotThermalChimney
CALL SetupOutputVariable('Zone Thermal Chimney Volume Flow Rate [m3/s]', &
ThermalChimneyReport(Loop)%OverallTCVolumeFlow,'System','Average', &
ThermalChimneySys(Loop)%Name)
CALL SetupOutputVariable('Zone Thermal Chimney Mass Flow Rate [kg/s]', &
ThermalChimneyReport(Loop)%OverallTCMassFlow,'System','Average', &
ThermalChimneySys(Loop)%Name)
CALL SetupOutputVariable('Zone Thermal Chimney Outlet Temperature [C]', &
ThermalChimneyReport(Loop)%OutletAirTempThermalChim,'System','Average', &
ThermalChimneySys(Loop)%Name)
DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
CALL SetupOutputVariable('Zone Thermal Chimney Heat Loss Energy [J]', &
ZnRptThermChim(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%ThermalChimneyHeatLoss, &
'System','Sum',Zone(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%Name)
CALL SetupOutputVariable('Zone Thermal Chimney Heat Gain Energy [J]', &
ZnRptThermChim(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%ThermalChimneyHeatGain, &
'System','Sum',Zone(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%Name)
CALL SetupOutputVariable('Zone Thermal Chimney Volume [m3]', &
ZnRptThermChim(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%ThermalChimneyVolume, &
'System','Sum',Zone(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%Name)
CALL SetupOutputVariable('Zone Thermal Chimney Mass [kg]', &
ZnRptThermChim(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%ThermalChimneyMass, &
'System','Sum',Zone(ThermalChimneySys(Loop)%ZonePtr(TCZoneNum))%Name)
END DO ! DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
END DO ! DO Loop=1, TotThermalChimney
!! LKL-more renaming effort and code review might be possible here
! Check to make sure there is only one thermal chimney statement per zone
DO Loop = 1, TotThermalChimney
IF (ThermalChimneySys(Loop)%TotZoneToDistrib > 1) THEN
DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
IF ( ThermalChimneySys(Loop)%TotZoneToDistrib >= (TCZoneNum+1) ) THEN
DO TCZoneNum1 = TCZoneNum+1, ThermalChimneySys(Loop)%TotZoneToDistrib
IF ( ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop)%ZonePtr(TCZoneNum1) ) THEN
CALL ShowSevereError('Only one ZoneThermalChimney object allowed per zone but zone ' &
//TRIM(ThermalChimneySys(Loop)%ZoneName(TCZoneNum))// &
' has two ZoneThermalChimney objects associated with it')
ErrorsFound = .TRUE.
END IF
END DO
DO TCZoneNum1 = 1, TCZoneNum-1
IF ( ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop)%ZonePtr(TCZoneNum1) ) THEN
CALL ShowSevereError('Only one ZoneThermalChimney object allowed per zone but zone ' &
//TRIM(ThermalChimneySys(Loop)%ZoneName(TCZoneNum))// &
' has two ZoneThermalChimney objects associated with it')
ErrorsFound = .TRUE.
END IF
END DO
ELSE ! IF ( ThermalChimneySys(Loop)%TotZoneToDistrib >= (TCZoneNum+1) ) THEN
DO TCZoneNum1 = 1, TCZoneNum-1
IF ( ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop)%ZonePtr(TCZoneNum1) ) THEN
CALL ShowSevereError('Only one ZoneThermalChimney object allowed per zone but zone ' &
//TRIM(ThermalChimneySys(Loop)%ZoneName(TCZoneNum))// &
' has two ZoneThermalChimney objects associated with it')
ErrorsFound = .TRUE.
END IF
END DO
END IF ! IF ( ThermalChimneySys(Loop)%TotZoneToDistrib >= (TCZoneNum+1) ) THEN
END DO ! DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
END IF ! IF (ThermalChimneySys(Loop)%TotZoneToDistrib > 1) THEN
END DO ! DO Loop = 1, TotThermalChimney
! Check to make sure there is only one thermal chimney statement per zone
IF (TotThermalChimney > 1) THEN
DO Loop = 1, TotThermalChimney
IF ( TotThermalChimney >= (Loop+1) ) THEN
DO Loop1 = Loop+1, TotThermalChimney
DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
DO TCZoneNum1 = 1, ThermalChimneySys(Loop1)%TotZoneToDistrib
IF ( ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop1)%ZonePtr(TCZoneNum1) ) THEN
CALL ShowSevereError('Only one ZoneThermalChimney object allowed per zone but zone ' &
//TRIM(ThermalChimneySys(Loop)%ZoneName(TCZoneNum))// &
' has two ZoneThermalChimney objects associated with it')
ErrorsFound = .TRUE.
END IF
END DO
END DO
END DO
DO Loop1 = 1, Loop-1
DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
DO TCZoneNum1 = 1, ThermalChimneySys(Loop1)%TotZoneToDistrib
IF ( ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop1)%ZonePtr(TCZoneNum1) ) THEN
CALL ShowSevereError('Only one ZoneThermalChimney object allowed per zone but zone ' &
//TRIM(ThermalChimneySys(Loop)%ZoneName(TCZoneNum))// &
' has two ZoneThermalChimney objects associated with it')
ErrorsFound = .TRUE.
END IF
END DO
END DO
END DO
ELSE ! IF ( TotThermalChimney >= (Loop+1) ) THEN
DO Loop1 = 1, Loop-1
DO TCZoneNum = 1, ThermalChimneySys(Loop)%TotZoneToDistrib
DO TCZoneNum1 = 1, ThermalChimneySys(Loop1)%TotZoneToDistrib
IF ( ThermalChimneySys(Loop)%ZonePtr(TCZoneNum) == ThermalChimneySys(Loop1)%ZonePtr(TCZoneNum1) ) THEN
CALL ShowSevereError('Only one ZoneThermalChimney object allowed per zone but zone ' &
//TRIM(ThermalChimneySys(Loop)%ZoneName(TCZoneNum))// &
' has two ZoneThermalChimney objects associated with it')
ErrorsFound = .TRUE.
END IF
END DO
END DO
END DO
END IF ! IF ( TotThermalChimney >= (Loop+1) ) THEN
END DO ! DO Loop = 1, TotThermalChimney
END IF ! IF (TotThermalChimney > 1) THEN
IF (ErrorsFound) THEN
CALL ShowFatalError(trim(cCurrentModuleObject)//' Errors found in input. Preceding condition(s) cause termination.')
END IF
RETURN
END SUBROUTINE GetThermalChimney