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 | ||
---|---|---|---|---|---|---|
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 GetProjectControlData(ErrorsFound)
! SUBROUTINE INFORMATION:
! AUTHOR Linda Lawrie
! DATE WRITTEN October 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! This subroutine gets the project control data before the rest of the building data (such as
! materials) is obtained.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! This routine gets the following objects:
! BUILDING
! INSIDE CONVECTION ALGORITHM
! OUTSIDE CONVECTION ALGORITHM
! SOLUTION ALGORITHM
! ASHRAE Handbook of Fundamentals, Chap 16, for the setting of Site Atmospheric defaults based
! on terrain.
! ZoneAirHeatBalanceAlgorithm, Added by L. Gu, 12/09
! ZoneAirContaminantBalance, Added by L. Gu, 06/10
! USE STATEMENTS:
USE General, ONLY: RoundSigDigits
USE DataSystemVariables, ONLY: lMinimalShadowing
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ErrorsFound ! Set to true if errors detected during getting data
! SUBROUTINE PARAMETER DEFINITIONS:
CHARACTER(len=*), PARAMETER :: RoutineName='GetProjectControlData: '
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
CHARACTER(len=MaxNameLength), DIMENSION(4) :: AlphaName
REAL(r64), DIMENSION(5) :: BuildingNumbers
INTEGER :: NumAlpha, NumNumber
INTEGER :: IOStat
INTEGER :: NumObjects
INTEGER :: TMP
!Assign the values to the building data
CurrentModuleObject='Building'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem(CurrentModuleObject,1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
! Building Name (remove certain characters)
BuildingName=AlphaName(1)
TMP=INDEX(BuildingName,CHAR(1))
DO WHILE (TMP /= 0)
BuildingName(TMP:TMP)=','
TMP=INDEX(BuildingName,CHAR(1))
END DO
TMP=INDEX(BuildingName,CHAR(2))
DO WHILE (TMP /= 0)
BuildingName(TMP:TMP)='!'
TMP=INDEX(BuildingName,CHAR(2))
END DO
TMP=INDEX(BuildingName,CHAR(3))
DO WHILE (TMP /= 0)
BuildingName(TMP:TMP)='\'
TMP=INDEX(BuildingName,CHAR(3))
END DO
! Building Azimuth (no validation)
BuildingAzimuth=MOD(BuildingNumbers(1),360.d0)
! Terrain
IF (AlphaName(2) == 'COUNTRY' .or. AlphaName(2) == '1') THEN
SiteWindExp = 0.14d0
SiteWindBLHeight = 270.d0
AlphaName(2)='Country'
ELSEIF (AlphaName(2) == 'SUBURBS' .or. AlphaName(2) == '2' .or. AlphaName(2) == 'SUBURB') THEN
SiteWindExp = 0.22d0
SiteWindBLHeight = 370.d0
AlphaName(2)='Suburbs'
ELSEIF (AlphaName(2) == 'CITY' .or. AlphaName(2) == '3') THEN
SiteWindExp = 0.33d0
SiteWindBLHeight = 460.d0
AlphaName(2)='City'
ELSEIF (AlphaName(2) == 'OCEAN') THEN
SiteWindExp = 0.10d0
SiteWindBLHeight = 210.d0
AlphaName(2)='Ocean'
ELSEIF (AlphaName(2) == 'URBAN') THEN
SiteWindExp = 0.22d0
SiteWindBLHeight = 370.d0
AlphaName(2)='Urban'
ELSE
CALL ShowSevereError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cAlphaFieldNames(2))// &
' invalid='//TRIM(AlphaName(2)))
SiteWindExp = 0.14d0
SiteWindBLHeight = 270.d0
AlphaName(2)=TRIM(AlphaName(2))//'-invalid'
ErrorsFound=.true.
ENDIF
! Loads Convergence Tolerance Value
LoadsConvergTol=BuildingNumbers(2)
IF (LoadsConvergTol <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cNumericFieldNames(2))// &
' value invalid, ['// &
TRIM(RoundSigDigits(LoadsConvergTol,3))//']')
ErrorsFound=.true.
ENDIF
! Temperature Convergence Tolerance Value
TempConvergTol=BuildingNumbers(3)
IF (TempConvergTol <= 0.0d0) THEN
CALL ShowSevereError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cNumericFieldNames(2))// &
' value invalid, ['// &
TRIM(RoundSigDigits(TempConvergTol,3))//']')
ErrorsFound=.true.
ENDIF
! Solar Distribution
IF (AlphaName(3)(1:3) == 'MIN' .or. AlphaName(3) == '-1' .or. lMinimalShadowing) THEN
SolarDistribution=MinimalShadowing
AlphaName(3)='MinimalShadowing'
CalcSolRefl = .FALSE.
ELSEIF (AlphaName(3) == 'FULLEXTERIOR' .or. AlphaName(3) == '0') THEN
SolarDistribution=FullExterior
AlphaName(3)='FullExterior'
CalcSolRefl = .FALSE.
ELSEIF (AlphaName(3) == 'FULLINTERIORANDEXTERIOR' .or. AlphaName(3) == '1') THEN
SolarDistribution=FullInteriorExterior
AlphaName(3)='FullInteriorAndExterior'
CalcSolRefl = .FALSE.
ELSEIF (AlphaName(3) == 'FULLEXTERIORWITHREFLECTIONS') THEN
SolarDistribution=FullExterior
AlphaName(3)='FullExteriorWithReflectionsFromExteriorSurfaces'
CalcSolRefl = .TRUE.
ELSEIF (AlphaName(3) == 'FULLINTERIORANDEXTERIORWITHREFLECTIONS') THEN
SolarDistribution=FullInteriorExterior
AlphaName(3)='FullInteriorAndExteriorWithReflectionsFromExteriorSurfaces'
CalcSolRefl = .TRUE.
ELSE
CALL ShowSevereError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cAlphaFieldNames(3))// &
' invalid='//TRIM(AlphaName(3)))
ErrorsFound=.true.
AlphaName(3)=TRIM(AlphaName(3))//'-invalid'
ENDIF
! Maximum Number of Warmup Days
IF (.not. lNumericFieldBlanks(4)) THEN
MaxNumberOfWarmupDays=BuildingNumbers(4)
IF (MaxNumberOfWarmupDays <= 0) THEN
CALL ShowSevereError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cNumericFieldNames(4))// &
' invalid, ['// &
TRIM(RoundSigDigits(MaxNumberOfWarmupDays))//'], '// &
trim(RoundSigDIgits(DefaultMaxNumberOfWarmupDays))//' will be used')
MaxNumberOfWarmupDays=DefaultMaxNumberOfWarmupDays
ENDIF
ELSE
MaxNumberOfWarmupDays=DefaultMaxNumberOfWarmupDays
ENDIF
! Minimum Number of Warmup Days
IF (.not. lNumericFieldBlanks(5)) THEN
MinNumberOfWarmupDays=BuildingNumbers(5)
IF (MinNumberOfWarmupDays <= 0) THEN
CALL ShowWarningError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cNumericFieldNames(5))// &
' invalid, ['// &
TRIM(RoundSigDigits(MinNumberOfWarmupDays))//'], '// &
trim(RoundSigDIgits(DefaultMinNumberOfWarmupDays))//' will be used')
MinNumberOfWarmupDays=DefaultMinNumberOfWarmupDays
ENDIF
ELSE
MinNumberOfWarmupDays=DefaultMinNumberOfWarmupDays
ENDIF
IF (MinNumberOfWarmupDays > MaxNumberOfWarmupDays) THEN
CALL ShowWarningError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cNumericFieldNames(5))// &
' ['//TRIM(RoundSigDigits(MinNumberOfWarmupDays))//'] '// &
' is greater than '//trim(cNumericFieldNames(4))//' ['// &
TRIM(RoundSigDigits(MaxNumberOfWarmupDays))//'], '// &
TRIM(RoundSigDigits(MinNumberOfWarmupDays))//' will be used.')
MaxNumberOfWarmupDays=MinNumberOfWarmupDays
ENDIF
IF (MinNumberOfWarmupDays < 6) THEN
CALL ShowWarningError(RoutineName//trim(CurrentModuleObject)//': '//TRIM(cNumericFieldNames(5))// &
' potentially invalid. '// &
'Experience has shown that most files will converge within '//trim(RoundSigDigits(DefaultMaxNumberOfWarmupDays))// &
' warmup days. ')
CALL ShowContinueError('...Choosing less than '//trim(RoundSigDigits(DefaultMinNumberOfWarmupDays))// &
' warmup days may have adverse effects on the simulation results, '// &
'particularly design day simulations. ')
CALL ShowContinueError('...Users should only alter this default if they are certain that '// &
'less than '//trim(RoundSigDigits(DefaultMinNumberOfWarmupDays))// &
' warmup days is appropriate for a particular file. ')
CALL ShowContinueError('...Verify that convergence to desired results are achieved. You can report values'// &
' during warmup days to ascertain convergence.')
ENDIF
ELSE
CALL ShowSevereError(RoutineName//' A '//TRIM(CurrentModuleObject)//' Object must be entered.')
ErrorsFound=.true.
BuildingName='NOT ENTERED'
AlphaName(2)='NOT ENTERED'
AlphaName(3)='NOT ENTERED'
MaxNumberOfWarmupDays=DefaultMaxNumberOfWarmupDays
MinNumberOfWarmupDays=DefaultMinNumberOfWarmupDays
ENDIF
! Write Building Information to the initialization output file
Write(OutputFileInits,721)
721 Format('! <Building Information>, Building Name,North Axis {deg},Terrain, ', &
' Loads Convergence Tolerance Value,Temperature Convergence Tolerance Value, ', &
' Solar Distribution,Maximum Number of Warmup Days,Minimum Number of Warmup Days')
Write(OutputFileInits,720) TRIM(BuildingName),trim(RoundSigDigits(BuildingAzimuth,3)),TRIM(AlphaName(2)), &
trim(RoundSigDigits(LoadsConvergTol,5)),trim(RoundSigDigits(TempConvergTol,5)), &
TRIM(AlphaName(3)),trim(RoundSigDigits(MaxNumberOfWarmupDays)),trim(RoundSigDigits(MinNumberOfWarmupDays))
720 Format(' Building Information',8(',',A))
! Above should be validated...
CurrentModuleObject='SurfaceConvectionAlgorithm:Inside'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem(CurrentModuleObject,1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
SELECT CASE (AlphaName(1))
CASE ('SIMPLE')
DefaultInsideConvectionAlgo=ASHRAESimple
AlphaName(1)='Simple'
CASE ('TARP','DETAILED')
DefaultInsideConvectionAlgo=ASHRAETARP
IF (AlphaName(1) == 'DETAILED') THEN
CALL ShowSevereError('GetInsideConvectionAlgorithm: Deprecated value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to TARP, entered value='//TRIM(AlphaName(1)))
ENDIF
AlphaName(1)='TARP'
CASE ('CEILINGDIFFUSER')
DefaultInsideConvectionAlgo=CeilingDiffuser
AlphaName(1)='CeilingDiffuser'
CASE ('TROMBEWALL')
DefaultInsideConvectionAlgo=TrombeWall
CALL ShowSevereError('GetInsideConvectionAlgorithm: TrombeWall has been used as a global definition.'// &
' This is a zone oriented value. Will be illegal in the future.')
AlphaName(1)='TrombeWall'
CASE ('ADAPTIVECONVECTIONALGORITHM')
DefaultInsideConvectionAlgo=AdaptiveConvectionAlgorithm
AlphaName(1)='AdaptiveConvectionAlgorithm'
CASE DEFAULT
CALL ShowWarningError('GetInsideConvectionAlgorithm: Invalid value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to TARP, invalid value='//TRIM(AlphaName(1)))
DefaultInsideConvectionAlgo=ASHRAETARP
AlphaName(1)='TARP'
END SELECT
ELSE
! default value, if not specified
DefaultInsideConvectionAlgo=ASHRAETARP
AlphaName(1)='TARP'
ENDIF
Write(OutputFileInits,722) TRIM(AlphaName(1))
722 Format('! <Inside Convection Algorithm>, Algorithm {Simple | TARP | CeilingDiffuser | AdaptiveConvectionAlgorithm}',/, &
'Inside Convection Algorithm,',A)
!Get only the first (if more were input)
CurrentModuleObject='SurfaceConvectionAlgorithm:Outside'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem('SurfaceConvectionAlgorithm:Outside',1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
SELECT CASE (AlphaName(1))
CASE ('SIMPLECOMBINED', 'SIMPLE')
DefaultOutsideConvectionAlgo=ASHRAESimple
IF (AlphaName(1) == 'SIMPLE') THEN
CALL ShowSevereError('GetOutsideConvectionAlgorithm: Deprecated value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to SimpleCombined, entered value='//TRIM(AlphaName(1)))
ENDIF
AlphaName(1)='SimpleCombined'
CASE ('TARP', 'DETAILED', 'BLAST')
DefaultOutsideConvectionAlgo=ASHRAETARP
IF (AlphaName(1) == 'DETAILED') THEN
CALL ShowSevereError('GetOutsideConvectionAlgorithm: Deprecated value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to TARP, entered value='//TRIM(AlphaName(1)))
ENDIF
IF (AlphaName(1) == 'BLAST') THEN
CALL ShowSevereError('GetOutsideConvectionAlgorithm: Deprecated value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to TARP, entered value='//TRIM(AlphaName(1)))
ENDIF
AlphaName(1)='TARP'
CASE ('MOWITT')
DefaultOutsideConvectionAlgo=MoWittHcOutside
AlphaName(1)='MoWitt'
CASE ('DOE-2','DOE2')
DefaultOutsideConvectionAlgo=DOE2HcOutside
IF (AlphaName(1) == 'DOE2') THEN
CALL ShowSevereError('GetOutsideConvectionAlgorithm: Deprecated value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to DOE-2, entered value='//TRIM(AlphaName(1)))
ENDIF
AlphaName(1)='DOE-2'
CASE ('ADAPTIVECONVECTIONALGORITHM')
DefaultOutsideConvectionAlgo=AdaptiveConvectionAlgorithm
AlphaName(1)='AdaptiveConvectionAlgorithm'
CASE DEFAULT
CALL ShowWarningError('GetOutsideConvectionAlgorithm: Invalid value for '//TRIM(CurrentModuleObject)//', '// &
'defaulting to DOE-2, invalid value='//TRIM(AlphaName(1)))
DefaultOutsideConvectionAlgo=DOE2HcOutside
AlphaName(1)='DOE-2'
END SELECT
ELSE
! default value, if not specified
DefaultOutsideConvectionAlgo=DOE2HcOutside
AlphaName(1)='DOE-2'
ENDIF
Write(OutputFileInits,723) TRIM(AlphaName(1))
723 Format('! <Outside Convection Algorithm>, ', &
'Algorithm {SimpleCombined | TARP | MoWitt | DOE-2 | AdaptiveConvectionAlgorithm}', /, &
'Outside Convection Algorithm,',A)
CurrentModuleObject='HeatBalanceAlgorithm'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem(CurrentModuleObject,1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
SELECT CASE (AlphaName(1))
!The default is CTF = 0. Then the moisture solution is EMPD =2
CASE ('CONDUCTIONTRANSFERFUNCTION','DEFAULT','CTF')
OverallHeatTransferSolutionAlgo = UseCTF
AlphaName(1)='CTF - Conduction Transfer Function'
CASE ('MOISTUREPENETRATIONDEPTHCONDUCTIONTRANSFERFUNCTION','EMPD')
OverallHeatTransferSolutionAlgo = UseEMPD
AlphaName(1)='EMPD - Effective Moisture Penetration Depth'
CASE ('CONDUCTIONFINITEDIFFERENCE','CONDFD','CONDUCTIONFINITEDIFFERENCEDETAILED')
OverallHeatTransferSolutionAlgo = UseCondFD
AlphaName(1)='CONDFD - Conduction Finite Difference'
IF (NumOfTimeStepInHour < 20) THEN
CALL ShowSevereError('GetSolutionAlgorithm: '//TRIM(CurrentModuleObject)//' '//TRIM(cAlphaFieldNames(1))// &
' is Conduction Finite Difference but Number of TimeSteps in Hour < 20, Value is '// &
TRIM(RoundSigDigits(NumOfTimeStepInHour))//'.')
CALL ShowContinueError('...Suggested minimum number of time steps in hour for '// &
'Conduction Finite Difference solutions is 20.'// &
' Errors or inaccurate calculations may occur.')
ENDIF
CASE ('COMBINEDHEATANDMOISTUREFINITEELEMENT','HAMT')
OverallHeatTransferSolutionAlgo = UseHAMT
AlphaName(1)='HAMT - Combined Heat and Moisture Transfer Finite Element'
IF (NumOfTimeStepInHour < 20) THEN
CALL ShowSevereError('GetSolutionAlgorithm: '//TRIM(CurrentModuleObject)//' '//TRIM(cAlphaFieldNames(1))// &
' is Combined Heat and Moisture Finite Element but Number of TimeSteps in Hour < 20, Value is '// &
TRIM(RoundSigDigits(NumOfTimeStepInHour))//'.')
CALL ShowContinueError('...Suggested minimum number of time steps in hour for '// &
'Combined Heat and Moisture Finite Element solutions is 20.'// &
' Errors or inaccurate calculations may occur.')
CALL ShowContinueError('...If the simulation crashes, look at material properties (esp porosity), '// &
'use timestep=60, or less layers in your constructions.')
ENDIF
CASE DEFAULT
OverallHeatTransferSolutionAlgo = UseCTF
AlphaName(1)='CTF - Conduction Transfer Function'
END SELECT
IF (NumNumber > 0) THEN
MaxSurfaceTempLimit=BuildingNumbers(1)
MaxSurfaceTempLimitBeforeFatal=MaxSurfaceTempLimit*2.5d0
IF (MaxSurfaceTempLimit < MinSurfaceTempLimit) THEN
ELSEIF (MaxSurfaceTempLimit < 0.0d0) THEN
MaxSurfaceTempLimit=DefaultSurfaceTempLimit
MaxSurfaceTempLimitBeforeFatal=MaxSurfaceTempLimit*2.5d0
ENDIF
ENDIF
IF ( .NOT. lNumericFieldBlanks(2)) THEN
LowHConvLimit = BuildingNumbers(2)
ENDIF
IF ( .NOT. lNumericFieldBlanks(3)) THEN
HighHConvLimit = BuildingNumbers(3)
ENDIF
ELSE
OverallHeatTransferSolutionAlgo = UseCTF
AlphaName(1)='ConductionTransferFunction'
MaxSurfaceTempLimit=DefaultSurfaceTempLimit
MaxSurfaceTempLimitBeforeFatal=MaxSurfaceTempLimit*2.5d0
ENDIF
ALLOCATE(HeatTransferAlgosUsed(1))
HeatTransferAlgosUsed(1) = OverallHeatTransferSolutionAlgo
! algorithm input checks now deferred until surface properties are read in,
! moved to SurfaceGeometry.f90 routine GetSurfaceHeatTransferAlgorithmOverrides
Write(OutputFileInits,724)
724 Format('! <Sky Radiance Distribution>, Value {Anisotropic}',/, &
'Sky Radiance Distribution,Anisotropic')
CurrentModuleObject='Compliance:Building'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem(CurrentModuleObject,1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
! Building Rotation for Appendix G
BuildingRotationAppendixG = MOD(BuildingNumbers(1),360.d0)
END IF
! A new object is added by L. Gu, 12/09
CurrentModuleObject='ZoneAirHeatBalanceAlgorithm'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem(CurrentModuleObject,1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
If (NumAlpha > 0) Then
SELECT CASE (AlphaName(1))
CASE ('3RDORDERBACKWARDDIFFERENCE','THIRDORDERBACKWARDDIFFERENCE')
ZoneAirSolutionAlgo = Use3rdOrder
AlphaName(1)='ThirdOrderBackwardDifference'
CASE ('ANALYTICALSOLUTION')
ZoneAirSolutionAlgo = UseAnalyticalSolution
AlphaName(1)='AnalyticalSolution'
CASE ('EULERMETHOD')
ZoneAirSolutionAlgo = UseEulerMethod
AlphaName(1)='EulerMethod'
CASE DEFAULT
ZoneAirSolutionAlgo = Use3rdOrder
AlphaName(1)='ThirdOrderBackwardDifference'
CALL ShowWarningError(TRIM(CurrentModuleObject)//': Invalid input of '//TRIM(cAlphaFieldNames(1))// &
'. The default choice is assigned = '//TRIM(AlphaName(1)))
CALL ShowContinueError('Valid choices are: ThirdOrderBackwardDifference, AnalyticalSolution, or EulerMethod.')
END SELECT
End If
ELSE
ZoneAirSolutionAlgo = Use3rdOrder
AlphaName(1)='ThirdOrderBackwardDifference'
ENDIF
! Write Solution Algorithm to the initialization output file for User Verification
Write(OutputFileInits,726)
Write(OutputFileInits,727) TRIM(AlphaName(1))
726 Format('! <Zone Air Solution Algorithm>, Value {ThirdOrderBackwardDifference | AnalyticalSolution | EulerMethod}')
727 Format(' Zone Air Solution Algorithm, ',A)
! A new object is added by L. Gu, 06/10
CurrentModuleObject='ZoneAirContaminantBalance'
NumObjects=GetNumObjectsFound(CurrentModuleObject)
IF (NumObjects > 0) THEN
CALL GetObjectItem(CurrentModuleObject,1,AlphaName,NumAlpha,BuildingNumbers,NumNumber,IOStat, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
If (NumAlpha > 0) Then
SELECT CASE (AlphaName(1))
CASE ('YES')
Contaminant%CO2Simulation = .TRUE.
Contaminant%SimulateContaminants = .TRUE.
CASE ('NO')
Contaminant%CO2Simulation = .FALSE.
CASE DEFAULT
Contaminant%CO2Simulation = .FALSE.
AlphaName(1)='NO'
CALL ShowWarningError(TRIM(CurrentModuleObject)//': Invalid input of '//TRIM(cAlphaFieldNames(1))// &
'. The default choice is assigned = NO')
END SELECT
End If
If (NumAlpha .EQ. 1 .AND. Contaminant%CO2Simulation) Then
If (Contaminant%CO2Simulation) Then
CALL ShowSevereError(TRIM(CurrentModuleObject)//', '//TRIM(cAlphaFieldNames(2))//' is required and not given.')
ErrorsFound=.true.
End If
ElseIf (NumAlpha > 1 .AND. Contaminant%CO2Simulation) Then
Contaminant%CO2OutdoorSchedPtr = GetScheduleIndex(AlphaName(2))
IF (Contaminant%CO2OutdoorSchedPtr == 0) THEN
CALL ShowSevereError(TRIM(CurrentModuleObject)//', '//TRIM(cAlphaFieldNames(2))//' not found: '//TRIM(AlphaName(2)))
ErrorsFound=.true.
ENDIF
End If
If (NumAlpha > 2) Then
SELECT CASE (AlphaName(3))
CASE ('YES')
Contaminant%GenericContamSimulation = .TRUE.
If (.NOT. Contaminant%CO2Simulation) Contaminant%SimulateContaminants = .TRUE.
CASE ('NO')
Contaminant%GenericContamSimulation = .FALSE.
CASE DEFAULT
Contaminant%GenericContamSimulation = .FALSE.
AlphaName(3)='NO'
CALL ShowWarningError(TRIM(CurrentModuleObject)//': Invalid input of '//TRIM(cAlphaFieldNames(3))// &
'. The default choice is assigned = NO')
END SELECT
If (NumAlpha .EQ. 3 .AND. Contaminant%GenericContamSimulation) Then
If (Contaminant%GenericContamSimulation) Then
CALL ShowSevereError(TRIM(CurrentModuleObject)//', '//TRIM(cAlphaFieldNames(4))//' is required and not given.')
ErrorsFound=.true.
End If
ElseIf (NumAlpha > 3 .AND. Contaminant%GenericContamSimulation) Then
Contaminant%GenericContamOutdoorSchedPtr = GetScheduleIndex(AlphaName(4))
IF (Contaminant%GenericContamOutdoorSchedPtr == 0) THEN
CALL ShowSevereError(TRIM(CurrentModuleObject)//', '//TRIM(cAlphaFieldNames(4))//' not found: '//TRIM(AlphaName(4)))
ErrorsFound=.true.
ENDIF
End If
End If
ELSE
Contaminant%SimulateContaminants = .FALSE.
Contaminant%CO2Simulation = .FALSE.
Contaminant%GenericContamSimulation = .FALSE.
AlphaName(1)='NO'
AlphaName(3)='NO'
ENDIF
Write(OutputFileInits,728)
If (Contaminant%SimulateContaminants .AND. Contaminant%CO2Simulation) Then
Write(OutputFileInits,730) 'Yes',TRIM(AlphaName(1))
ELSE
Write(OutputFileInits,730) 'No','N/A'
END IF
728 Format('! <Zone Air Contaminant Balance Simulation>, Simulation {Yes/No}, Carbon Dioxide Concentration')
730 Format(' Zone Air Carbon Dioxide Balance Simulation, ',A,',',A)
Write(OutputFileInits,729)
If (Contaminant%SimulateContaminants .AND. Contaminant%GenericContamSimulation) Then
Write(OutputFileInits,731) 'Yes',TRIM(AlphaName(3))
ELSE
Write(OutputFileInits,731) 'No','N/A'
END IF
729 Format('! <Zone Air Contaminant Balance Simulation>, Simulation {Yes/No}, Generic Contaminant Concentration')
731 Format(' Zone Air Generic Contaminant Balance Simulation, ',A,',',A)
RETURN
END SUBROUTINE GetProjectControlData