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 GetHTSurfExtVentedCavityData(ErrorsFound )
! SUBROUTINE INFORMATION:
! AUTHOR BGriffith
! DATE WRITTEN January 2005
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! load input data for Exterior Vented Cavity Special case for heat transfer surfaces
! METHODOLOGY EMPLOYED:
! usual E+ input processes
! REFERENCES:
! derived from SUBROUTINE GetTranspiredCollectorInput
! USE STATEMENTS:
USE DataIPShortCuts
USE InputProcessor, ONLY: GetNumObjectsFound, GetObjectItem, GetObjectDefMaxArgs, FindItemInList , &
SameString, VerifyName
USE General, ONLY: TrimSigDigits
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
LOGICAL, INTENT(INOUT) :: ErrorsFound ! Error flag indicator (true if errors found)
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: Item ! Item to be "gotten"
INTEGER :: NumAlphas ! Number of Alphas for each GetObjectItem call
INTEGER :: NumNumbers ! Number of Numbers for each GetObjectItem call
INTEGER :: MaxNumAlphas !argument for call to GetObjectDefMaxArgs
INTEGER :: MaxNumNumbers !argument for call to GetObjectDefMaxArgs
INTEGER :: Dummy !argument for call to GetObjectDefMaxArgs
INTEGER :: IOStatus ! Used in GetObjectItem
INTEGER :: Found
INTEGER :: AlphaOffset !local temp var
CHARACTER(len=MaxNameLength) :: Roughness
INTEGER :: thisSurf ! do loop counter
REAL(r64) :: AvgAzimuth ! temp for error checking
REAL(r64) :: AvgTilt ! temp for error checking
INTEGER :: SurfID ! local surface "pointer"
LOGICAL :: IsBlank
LOGICAL :: ErrorInName
cCurrentModuleObject='SurfaceProperty:ExteriorNaturalVentedCavity'
CALL GetObjectDefMaxArgs(cCurrentModuleObject,Dummy, MaxNumAlphas,MaxNumNumbers)
IF (MaxNumNumbers /= 8) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//': Object Definition indicates '// &
'not = 8 Number Objects, Number Indicated='// &
TRIM(TrimSigDigits(MaxNumNumbers)))
ErrorsFound=.true.
ENDIF
TotExtVentCav = GetNumObjectsFound(cCurrentModuleObject)
ALLOCATE(ExtVentedCavity(TotExtVentCav))
DO Item=1,TotExtVentCav
CALL GetObjectItem(cCurrentModuleObject,Item,cAlphaArgs,NumAlphas,rNumericArgs,NumNumbers,IOStatus, &
AlphaBlank=lAlphaFieldBlanks,NumBlank=lNumericFieldBlanks, &
AlphaFieldnames=cAlphaFieldNames,NumericFieldNames=cNumericFieldNames)
! first handle cAlphaArgs
ErrorInName=.false.
IsBlank=.false.
CALL VerifyName(cAlphaArgs(1),ExtVentedCavity%Name,Item-1,ErrorInName,IsBlank,TRIM(cCurrentModuleObject)//' Name')
IF (ErrorInName) THEN
CALL ShowContinueError('...cannot not duplicate other names')
ErrorsFound=.true.
CYCLE
ENDIF
ExtVentedCavity(Item)%Name = cAlphaArgs(1)
ExtVentedCavity(Item)%OSCMName = cAlphaArgs(2)
IF (.not. lAlphaFieldBlanks(2)) THEN
Found = FindItemInList(ExtVentedCavity(Item)%OSCMName,OSCM%Name,TotOSCM)
IF (Found == 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(2))//'="'//TRIM(cAlphaArgs(2))//'".')
ErrorsFound=.true.
ENDIF
ELSE
Found=0
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(2))//' cannot be blank.')
ErrorsFound=.true.
ENDIF
ExtVentedCavity(Item)%OSCMPtr = Found
Roughness = cAlphaArgs(3)
!Select the correct Number for the associated ascii name for the roughness type
IF (SameString(Roughness,'VeryRough')) ExtVentedCavity(Item)%BaffleRoughness=VeryRough
IF (SameString(Roughness,'Rough')) ExtVentedCavity(Item)%BaffleRoughness=Rough
IF (SameString(Roughness,'MediumRough')) ExtVentedCavity(Item)%BaffleRoughness=MediumRough
IF (SameString(Roughness,'MediumSmooth')) ExtVentedCavity(Item)%BaffleRoughness=MediumSmooth
IF (SameString(Roughness,'Smooth')) ExtVentedCavity(Item)%BaffleRoughness=Smooth
IF (SameString(Roughness,'VerySmooth')) ExtVentedCavity(Item)%BaffleRoughness=VerySmooth
! Was it set?
IF (ExtVentedCavity(Item)%BaffleRoughness == 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(3))//'="'//TRIM(cAlphaArgs(3)))
ErrorsFound=.true.
ENDIF
AlphaOffset = 3
ExtVentedCavity(Item)%NumSurfs = NumAlphas - AlphaOffset
IF (ExtVentedCavity(Item)%NumSurfs == 0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", no underlying surfaces specified. Must have at least one.')
ErrorsFound = .true.
CYCLE
ENDIF
ALLOCATE(ExtVentedCavity(Item)%SurfPtrs(ExtVentedCavity(Item)%NumSurfs))
ExtVentedCavity(Item)%SurfPtrs = 0
DO thisSurf = 1, ExtVentedCavity(Item)%NumSurfs
Found = FindItemInList(cAlphaArgs(thisSurf + AlphaOffset), Surface%Name, TotSurfaces)
If (Found == 0) Then
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(thisSurf + AlphaOffset))// &
'="'//TRIM(cAlphaArgs(thisSurf + AlphaOffset)))
ErrorsFound=.true.
CYCLE
ENDIF
! check that surface is appropriate, Heat transfer, Sun, Wind,
IF (.not. surface(Found)%HeatTransSurf) then
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(thisSurf + AlphaOffset))// &
'="'//TRIM(cAlphaArgs(thisSurf + AlphaOffset)))
CALL ShowContinueError('...because it is not a Heat Transfer Surface.')
ErrorsFound=.true.
CYCLE
ENDIF
IF (.not. surface(found)%ExtSolar) then
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(thisSurf + AlphaOffset))// &
'="'//TRIM(cAlphaArgs(thisSurf + AlphaOffset)))
CALL ShowContinueError('...because it is not exposed to Sun.')
ErrorsFound=.true.
CYCLE
ENDIF
IF (.not. surface(found)%ExtWind) then
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid '//TRIM(cAlphaFieldNames(thisSurf + AlphaOffset))// &
'="'//TRIM(cAlphaArgs(thisSurf + AlphaOffset)))
CALL ShowContinueError('...because it is not exposed to Wind.')
ErrorsFound=.true.
CYCLE
ENDIF
If(surface(found)%ExtBoundCond /= OtherSideCondModeledExt) Then
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", is invalid')
CALL ShowContinueError('...because '//TRIM(cAlphaFieldNames(thisSurf + AlphaOffset))// &
'="'//TRIM(cAlphaArgs(thisSurf + AlphaOffset))//'".')
CALL ShowContinueError('...is not an OtherSideConditionedModel surface.')
ErrorsFound=.true.
CYCLE
ENDIF
ExtVentedCavity(Item)%SurfPtrs(thisSurf) = Found
! now set info in Surface structure
Surface(Found)%ExtCavNum = Item
Surface(Found)%ExtCavityPresent = .true.
ENDDO
IF (ErrorsFound) CYCLE ! previous inner do loop may have detected problems that need to be cycle'd again to avoid crash
! now that we should have all the surfaces, do some preperations and checks.
! are they all similar tilt and azimuth? Issue warnings so people can do it if they really want
AvgAzimuth = SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Azimuth * Surface(ExtVentedCavity(Item)%SurfPtrs)%Area) &
/SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Area)
AvgTilt = SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Tilt * Surface(ExtVentedCavity(Item)%SurfPtrs)%Area) &
/SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Area)
DO thisSurf = 1, ExtVentedCavity(Item)%NumSurfs
SurfID = ExtVentedCavity(Item)%SurfPtrs(thisSurf)
If (ABS(Surface(SurfID)%Azimuth - AvgAzimuth) > 15.d0 ) Then
Call ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
', Surface '//TRIM(Surface(SurfID)%name)//' has Azimuth different from others in '// &
'the associated group.')
ENDIF
IF (ABS(Surface(SurfID)%Tilt - AvgTilt) > 10.d0 ) Then
Call ShowWarningError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
', Surface '//TRIM(Surface(SurfID)%name)//' has Tilt different from others in '// &
'the associated group.')
ENDIF
!test that there are no windows. Now allow windows
! If (Surface(SurfID)%GrossArea > Surface(SurfID)%Area) Then
! Call ShowWarningError('Surface '//TRIM(Surface(SurfID)%name)//' has a subsurface whose area is not being ' &
! //'subtracted in the group of surfaces associated with '//TRIM(ExtVentedCavity(Item)%Name))
! endif
ENDDO
ExtVentedCavity(Item)%Tilt = AvgTilt
ExtVentedCavity(Item)%Azimuth = AvgAzimuth
! find area weighted centroid.
ExtVentedCavity(Item)%Centroid%Z = &
SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Centroid%Z*Surface(ExtVentedCavity(Item)%SurfPtrs)%Area) &
/SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Area)
!now handle rNumericArgs from input object
ExtVentedCavity(Item)%Porosity = rNumericArgs(1)
ExtVentedCavity(Item)%LWEmitt = rNumericArgs(2)
ExtVentedCavity(Item)%SolAbsorp = rNumericArgs(3)
ExtVentedCavity(Item)%HdeltaNPL = rNumericArgs(4)
ExtVentedCavity(Item)%PlenGapThick = rNumericArgs(5)
IF (ExtVentedCavity(Item)%PlenGapThick <= 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid .')
ErrorsFound=.true.
CALL ShowContinueError('...because Plenum gap must be greater than Zero=['// &
TRIM(TrimSigDigits(rNumericArgs(5),2))//'].')
CYCLE
ENDIF
ExtVentedCavity(Item)%AreaRatio = rNumericArgs(6)
ExtVentedCavity(Item)%Cv = rNumericArgs(7)
ExtVentedCavity(Item)%Cd = rNumericArgs(8)
! Fill out data we now know
! sum areas of HT surface areas
ExtVentedCavity(Item)%ProjArea = SUM(Surface(ExtVentedCavity(Item)%SurfPtrs)%Area)
IF (ExtVentedCavity(Item)%ProjArea <= 0.0d0) THEN
CALL ShowSevereError(TRIM(cCurrentModuleObject)//'="'//TRIM(ExtVentedCavity(Item)%Name)// &
'", invalid .')
ErrorsFound=.true.
CALL ShowContinueError('...because gross area of underlying surfaces must be greater than Zero=['// &
TRIM(TrimSigDigits(ExtVentedCavity(Item)%ProjArea,2))//'].')
CYCLE
endif
ExtVentedCavity(Item)%ActualArea = ExtVentedCavity(Item)%ProjArea * ExtVentedCavity(Item)%AreaRatio
CALL SetupOutputVariable('Surface Exterior Cavity Baffle Surface Temperature [C]',ExtVentedCavity(Item)%Tbaffle, &
'System','Average',ExtVentedCavity(Item)%Name)
CALL SetupOutputVariable('Surface Exterior Cavity Air Drybulb Temperature [C]',ExtVentedCavity(Item)%TAirCav, &
'System','Average',ExtVentedCavity(Item)%Name)
CALL SetupOutputVariable('Surface Exterior Cavity Total Natural Ventilation Air Change Rate [ACH]', &
ExtVentedCavity(Item)%PassiveACH, &
'System','Average',ExtVentedCavity(Item)%Name)
CALL SetupOutputVariable('Surface Exterior Cavity Total Natural Ventilation Mass Flow Rate [kg/s]', &
ExtVentedCavity(Item)%PassiveMdotVent, &
'System','Average',ExtVentedCavity(Item)%Name)
CALL SetupOutputVariable('Surface Exterior Cavity Natural Ventilation from Wind Mass Flow Rate [kg/s]', &
ExtVentedCavity(Item)%PassiveMdotWind, &
'System','Average',ExtVentedCavity(Item)%Name)
CALL SetupOutputVariable('Surface Exterior Cavity Natural Ventilation from Buoyancy Mass Flow Rate [kg/s]', &
ExtVentedCavity(Item)%PassiveMdotTherm, &
'System','Average',ExtVentedCavity(Item)%Name)
ENDDO
RETURN
END SUBROUTINE GetHTSurfExtVentedCavityData