Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer | :: | ZoneNum |
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 DayltgAveInteriorReflectance(ZoneNum)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN July 1997
! MODIFIED Mar 2004, FCW: add calculation of following SurfaceWindow variables:
! ZoneAreaMinusThisSurf, ZoneAreaReflProdMinusThisSurf, RhoCeilingWall,
! RhoFloorWall, FractionUpgoing. Add calculation of ZoneDaylight%FloorVisRefl.
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Called by CalcDayltgCoefficients for each daylit zone. Determines total
! area and area-weighted average visible reflectance of
! all inside faces of the surfaces of a zone. In addition, finds
! area and average reflectance of interzone, underground and exterior
! heat-transfer surfaces in the following categories: floor (tilt > 170 deg),
! ceiling (tilt < 10 deg), and wall (10 < tilt < 170 deg).
! The window reflectance values used here assume the windows have no shading
! devices. This information is used in the calculation of the
! internally-reflected daylighting component.
! Finds total number of exterior windows in the space.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! Based on DOE-2.1E subroutine DAVREF
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER :: ZoneNum ! Zone number
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: IType ! Surface type/class
REAL(r64) :: AREA ! Inside surface area (m2)
REAL(r64) :: AInsTot ! Total inside surface area of a zone (m2)
REAL(r64) :: ARHTOT ! Sum over surfaces of AREA*(inside visible reflectance) (m2)
INTEGER :: ISurf ! Surface number
INTEGER :: IWin ! Window number
INTEGER :: ITILT ! Surface tilt category (1 = floor, 2 = wall, 3 = ceiling)
INTEGER :: IT ! Tilt index
REAL(r64) :: AR(3) ! Inside surface area sum for floor/wall/ceiling (m2)
REAL(r64) :: ARH(3) ! Inside surface area*reflectance sum for floor/wall/ceiling (m2)
REAL(r64) :: AP(3) ! Zone inside surface floor/wall/ceiling area without a selected
! floor/wall/ceiling (m2)
REAL(r64) :: ARHP(3) ! Zone inside surface floor/wall/ceiling area*reflectance without
! a selected floor/wall/ceiling (m2)
REAL(r64) :: ATWL ! Opaque surface area (m2)
REAL(r64) :: ARHTWL ! ATWL times inside visible reflectance of surface (m2)
INTEGER :: IWinDr ! Window/door surface number
REAL(r64) :: ETA ! Ratio of floor-to-window-center height and average floor-to-ceiling height
! FLOW:
! Total inside surface area, including windows
AInsTOT = 0.0d0
! Sum of products of inside surface area * vis reflectance
ARHTOT = 0.0d0
! Area sum and area * reflectance sum for different orientations
AR = 0.0d0
ARH = 0.0d0
! Loop over surfaces
DO ISurf = Zone(ZoneNum)%SurfaceFirst,Zone(ZoneNum)%SurfaceLast
IType = Surface(ISurf)%Class
! Error if window has multiplier > 1 since this causes incorrect illuminance calc
IF (IType == SurfaceClass_Window .AND. Surface(ISurf)%Multiplier > 1.0d0) THEN
IF (ZoneDaylight(ZoneNum)%TotalDaylRefPoints > 0) THEN
CALL ShowSevereError('DayltgAveInteriorReflectance: Multiplier > 1.0 for window '// &
trim(Surface(ISurf)%Name)//' in Zone='//trim(Surface(ISurf)%ZoneName))
CALL ShowContinueError('...not allowed since it is in a zone with daylighting.')
CALL ShowFatalError('Progrem terminates due to preceding conditions.')
ELSE
CALL ShowSevereError('DayltgAveInteriorReflectance: Multiplier > 1.0 for window '// &
trim(Surface(ISurf)%Name)//' in Zone='//trim(Surface(ISurf)%ZoneName))
CALL ShowContinueError('...an adjacent Zone has daylighting. Simulation cannot proceed.')
CALL ShowFatalError('Progrem terminates due to preceding conditions.')
ENDIF
ENDIF
IF (IType == SurfaceClass_Wall.OR.IType == SurfaceClass_Floor.OR.IType == SurfaceClass_Roof &
.OR.IType == SurfaceClass_Window.OR.IType == SurfaceClass_Door) THEN
AREA = Surface(ISurf)%Area
! In following, FrameArea and DividerArea can be non-zero only for exterior windows
AInsTOT = AInsTOT + AREA + SurfaceWindow(ISurf)%FrameArea*(1.0d0+0.5d0*SurfaceWindow(ISurf)%ProjCorrFrIn) &
+ SurfaceWindow(ISurf)%DividerArea*(1.0d0+SurfaceWindow(ISurf)%ProjCorrDivIn)
ARHTOT = ARHTOT + AREA * Construct(Surface(ISurf)%Construction)%ReflectVisDiffBack + &
SurfaceWindow(ISurf)%FrameArea * (1.0d0+0.5d0*SurfaceWindow(ISurf)%ProjCorrFrIn) * &
(1.0d0-SurfaceWindow(ISurf)%FrameSolAbsorp) + &
SurfaceWindow(ISurf)%DividerArea * (1.0d0+SurfaceWindow(ISurf)%ProjCorrDivIn) * &
(1.0d0-SurfaceWindow(ISurf)%DividerSolAbsorp)
ITILT = 3 ! Ceiling
IF (Surface(ISurf)%Tilt > 10.0d0 .AND.Surface(ISurf)%Tilt < 170.0d0) ITILT = 2 ! Wall
IF (Surface(ISurf)%Tilt >= 170.0d0) ITILT = 1 ! Floor
AR(ITILT) = AR(ITILT) + AREA + &
SurfaceWindow(ISurf)%FrameArea * (1.0d0+0.5d0*SurfaceWindow(ISurf)%ProjCorrFrIn) &
+ SurfaceWindow(ISurf)%DividerArea * (1.0d0+SurfaceWindow(ISurf)%ProjCorrDivIn)
ARH(ITILT) = ARH(ITILT) + AREA*Construct(Surface(ISurf)%Construction)%ReflectVisDiffBack + &
SurfaceWindow(ISurf)%FrameArea * (1.0d0+0.5d0*SurfaceWindow(ISurf)%ProjCorrFrIn) * &
(1.0d0-SurfaceWindow(ISurf)%FrameSolAbsorp) + &
SurfaceWindow(ISurf)%DividerArea * (1.0d0+SurfaceWindow(ISurf)%ProjCorrDivIn) * &
(1.0d0-SurfaceWindow(ISurf)%DividerSolAbsorp)
END IF
END DO
! Average inside surface reflectance of zone
ZoneDaylight(ZoneNum)%AveVisDiffReflect = ARHTOT / AInsTOT
! Total inside surface area of zone
ZoneDaylight(ZoneNum)%TotInsSurfArea = AInsTOT
! Average floor visible reflectance
ZoneDaylight(ZoneNum)%FloorVisRefl = ARH(3) / (AR(3) + 1.d-6)
DO ISurf = Zone(ZoneNum)%SurfaceFirst,Zone(ZoneNum)%SurfaceLast
IType = Surface(ISurf)%Class
IF(IType == SurfaceClass_Wall.OR.IType == SurfaceClass_Floor.OR.IType == SurfaceClass_Roof) THEN
! Remove this surface from the zone inside surface area and area*reflectivity
! The resulting areas are AP(ITILT). The resulting area*reflectivity is ARHP(ITILT).
! Initialize gross area of surface (including subsurfaces)
ATWL = Surface(ISurf)%Area ! This is the surface area less subsurfaces
! Area * reflectance for this surface, excluding attached windows and doors
ARHTWL = Surface(ISurf)%Area * Construct(Surface(ISurf)%Construction)%ReflectVisDiffBack
! Tilt index
IF(Surface(ISurf)%Tilt > 45.0d0 .AND. Surface(ISurf)%Tilt < 135.0d0) THEN
ITILT = 2 ! Wall
ELSE IF(Surface(ISurf)%Tilt >= 135.0d0) THEN
ITILT = 1 ! Floor
ELSE
ITILT = 3 ! Ceiling
END IF
! Loop over windows and doors on this wall
DO IWinDr = Zone(ZoneNum)%SurfaceFirst,Zone(ZoneNum)%SurfaceLast
IF((Surface(IWinDr)%Class == SurfaceClass_Window .OR. Surface(IWinDr)%Class == SurfaceClass_Door) &
.AND. Surface(IWinDr)%BaseSurf == ISurf) THEN
ATWL = ATWL + Surface(IWinDr)%Area + &
SurfaceWindow(IWinDr)%FrameArea * (1.d0+0.5d0*SurfaceWindow(IWinDr)%ProjCorrFrIn) + &
SurfaceWindow(IWinDr)%DividerArea * (1.d0+SurfaceWindow(IWinDr)%ProjCorrDivIn)
ARHTWL = ARHTWL + Surface(IWinDr)%Area*Construct(Surface(IWinDr)%Construction)%ReflectVisDiffBack + &
SurfaceWindow(IWinDr)%FrameArea*(1.d0+0.5d0*SurfaceWindow(IWinDr)%ProjCorrFrIn)* &
(1.d0-SurfaceWindow(IWinDr)%FrameSolAbsorp) + &
SurfaceWindow(IWinDr)%DividerArea*(1.d0+SurfaceWindow(IWinDr)%ProjCorrDivIn)* &
(1.d0-SurfaceWindow(IWinDr)%DividerSolAbsorp)
END IF
END DO
! Inside surface area of floor, walls and ceilings, minus surface ISurf and its subsurfaces
DO IT = 1,3
IF(IT == ITILT) THEN
AP(IT) = AR(IT) - ATWL
ARHP(IT) = ARH(IT) - ARHTWL
ELSE
AP(IT) = AR(IT)
ARHP(IT) = ARH(IT)
END IF
END DO
SurfaceWindow(ISurf)%ZoneAreaMinusThisSurf = AP
SurfaceWindow(ISurf)%ZoneAreaReflProdMinusThisSurf = ARHP
END IF
END DO ! End of loop over opaque surfaces in zone
DO IWin = Zone(ZoneNum)%SurfaceFirst,Zone(ZoneNum)%SurfaceLast
IF(Surface(IWin)%Class == SurfaceClass_Window) THEN
ISurf = Surface(IWin)%BaseSurf
! Ratio of floor-to-window-center height and average floor-to-ceiling height
ETA = MAX(0.0d0, MIN(1.0d0,(SurfaceWindow(IWin)%WinCenter(3) - Zone(ZoneNum)%OriginZ) * &
Zone(ZoneNum)%FloorArea / Zone(ZoneNum)%Volume))
AP = SurfaceWindow(ISurf)%ZoneAreaMinusThisSurf
ARHP = SurfaceWindow(ISurf)%ZoneAreaReflProdMinusThisSurf
! Average reflectance seen by light moving up (RhoCeilingWall) and down (RhoFloorWall)
! across horizontal plane through center of window
SurfaceWindow(IWin)%RhoCeilingWall = (ARHP(2) * (1.d0 - ETA) + ARHP(3)) / (AP(2) * (1.d0 - ETA) + AP(3) + 1.0d-5)
SurfaceWindow(IWin)%RhoFloorWall = (ARHP(2) * ETA + ARHP(1)) / (AP(2) * ETA + AP(1) + 1.d-9)
! Angle factor for windows with diffusing shades. SurfaceWindow(IWin)%FractionUpgoing is
! fraction of light from the shade that goes up toward ceiling and upper part of walls.
! 1 - SurfaceWindow(IWin)%FractionUpgoing is fraction that goes down toward floor and lower part of walls.
SurfaceWindow(IWin)%FractionUpgoing = Surface(IWin)%Tilt/180.0d0
! Daylighting shelf simplication: All light goes up to the ceiling regardless of orientation of shelf
IF(Surface(IWin)%Shelf > 0) THEN
IF (Shelf(Surface(IWin)%Shelf)%InSurf > 0) SurfaceWindow(IWin)%FractionUpgoing = 1.0d0
END IF
END IF
END DO
RETURN
END SUBROUTINE DayltgAveInteriorReflectance