Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | SurfNum | |||
integer, | intent(in) | :: | FrDivNum | |||
integer, | intent(in) | :: | HourNum |
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 CalcFrameDividerShadow(SurfNum,FrDivNum,HourNum)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN June 2000
! MODIFIED Aug 2000, FW: add effective shadowing by inside
! projections
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Called by CalcPerSolarBeam for wholly or partially sunlit exterior windows
! with a frame and/or divider. Using beam solar profile angles,
! calculates fraction of glass shaded by exterior frame and divider projections,
! The frame and divider profiles are assumed to be rectangular.
!
! A similar shadowing approach is used to calculate the fraction of glass area
! that produces beam solar illumination on interior frame and divider projections.
! This fraction is used in CalcWinFrameAndDividerTemps to determine the
! beam solar absorbed by inside projections. Beam solar reflected by inside projections
! is assumed to stay in the zone (as beam solar) although in actuality roughly
! half of this is reflected back onto the glass and the half that is reflected
! into the zone is diffuse.
!
! For multipane glazing the effect of solar absorbed by the exposed portion of
! frame or divider between the panes is not calculated. Beam solar incident on
! these portions is assumed to be transmitted into the zone unchanged.
!
! The shadowing of diffuse solar radiation by projections is not considered.
!
! REFERENCES: na
! USE STATEMENTS: na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER,INTENT(IN) :: SurfNum ! Surface number
INTEGER,INTENT(IN) :: FrDivNum ! Frame/divider number
INTEGER,INTENT(IN) :: HourNum ! Hour number
! SUBROUTINE PARAMETER DEFINITIONS: na
! INTERFACE BLOCK SPECIFICATIONS: na
! DERIVED TYPE DEFINITIONS: na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: ElevSun ! Sun elevation; angle between sun and horizontal
REAL(r64) :: ElevWin ! Window elevation: angle between window outward normal and horizontal
REAL(r64) :: AzimWin ! Window azimuth (radians)
REAL(r64) :: AzimSun ! Sun azimuth (radians)
REAL(r64) :: ProfileAngHor ! Solar profile angle (radians) for horizontally oriented projections
! such as the top and bottom of a frame or horizontal dividers.
! This is the incidence angle in a plane that is normal to the window
! and parallel to the Y-axis of the window (the axis along
! which the height of the window is measured).
REAL(r64) :: ProfileAngVert ! Solar profile angle (radians) for vertically oriented projections
! such as the top and bottom of a frame or horizontal dividers.
! This is the incidence angle in a plane that is normal to the window
! and parallel to the X-axis of the window (the axis along
! which the width of the window is measured).
REAL(r64) :: TanProfileAngHor ! Tangent of ProfileAngHor
REAL(r64) :: TanProfileAngVert ! Tangent of ProfileAngVert
REAL(r64) :: FrWidth ! Frame width (m)
REAL(r64) :: DivWidth ! Divider width (m)
REAL(r64) :: FrProjOut ! Outside frame projection (m)
REAL(r64) :: DivProjOut ! Outside divider projection (m)
REAL(r64) :: FrProjIn ! Inside frame projection (m)
REAL(r64) :: DivProjIn ! Inside divider projection (m)
INTEGER :: NHorDiv ! Number of horizontal dividers
INTEGER :: NVertDiv ! Number of vertical dividers
REAL(r64) :: GlArea ! Glazed area (m2)
REAL(r64) :: Arealite ! Area of a single lite of glass (m2); glazed area, GlArea,
! if there is no divider (in which case there is only one lite).
REAL(r64) :: ArealiteCol ! Area of a vertical column of lites (m2)
REAL(r64) :: ArealiteRow ! Area of a horizontal row of lites (m2)
REAL(r64) :: AshVDout ! Shaded area from all vertical divider outside projections (m2)
REAL(r64) :: AshVDin ! Shaded area from all vertical divider inside projections (m2)
REAL(r64) :: AshHDout ! Shaded area from all horizontal divider outside projections (m2)
REAL(r64) :: AshHDin ! Shaded area from all horizontal divider inside projections (m2)
REAL(r64) :: AshVFout ! Shaded area from outside projection of vertical sides of frame (m2)
REAL(r64) :: AshVFin ! Shaded area from inside projection of vertical sides of frame (m2)
REAL(r64) :: AshHFout ! Shaded area from outside projection of horizontal sides
! (top) of frame (m2)
REAL(r64) :: AshHFin ! Shaded area from inside projection of horizontal sides
! (top) of frame (m2)
REAL(r64) :: AshDDover ! Divider/divider shadow overlap area (m2)
REAL(r64) :: AshFFover ! Frame/frame shadow overlap area (m2)
REAL(r64) :: AshFVDover ! Frame/vertical divider overlap area (m2)
REAL(r64) :: AshFHDover ! Frame/horizontal divider overlap area (m2)
REAL(r64) :: AshFDtotOut ! Total outside projection shadow area (m2)
REAL(r64) :: AshFDtotIn ! Total inside projection shadow area (m2)
REAL(r64) :: FracShFDOut ! Fraction of glazing shadowed by frame and divider
! outside projections
REAL(r64) :: FracShFDin ! Fraction of glazing that illuminates frame and divider
! inside projections with beam radiation
REAL(r64) :: WinNorm(3) ! Window outward normal unit vector
REAL(r64) :: ThWin ! Azimuth angle of WinNorm
REAL(r64) :: SunPrime(3) ! Projection of sun vector onto plane (perpendicular to
! window plane) determined by WinNorm and vector along
! baseline of window
REAL(r64) :: WinNormCrossBase(3) ! Cross product of WinNorm and vector along window baseline
IF (FrameDivider(FrDivNum)%FrameProjectionOut==0.0d0 .AND. &
FrameDivider(FrDivNum)%FrameProjectionIn==0.0d0 .AND. &
FrameDivider(FrDivNum)%DividerProjectionOut==0.0d0 .AND. &
FrameDivider(FrDivNum)%DividerProjectionIn==0.0d0) RETURN
FrProjOut = FrameDivider(FrDivNum)%FrameProjectionOut
FrProjIn = FrameDivider(FrDivNum)%FrameProjectionIn
DivProjOut = FrameDivider(FrDivNum)%DividerProjectionOut
DivProjIn = FrameDivider(FrDivNum)%DividerProjectionIn
GlArea = Surface(SurfNum)%Area
ElevWin = Piovr2 - Surface(SurfNum)%Tilt * DegToRadians
ElevSun = Piovr2 - ACOS(SUNCOS(3))
AzimWin = Surface(SurfNum)%Azimuth * DegToRadians
AzimSun = ATAN2(SUNCOS(1),SUNCOS(2))
ProfileAngHor = ATAN(SIN(ElevSun)/ABS(COS(ElevSun)*COS(AzimWin-AzimSun))) - ElevWin
IF(ABS(ElevWin) < 0.1d0) THEN ! Near-vertical window
ProfileAngVert = ABS(AzimWin-AzimSun)
ELSE
WinNorm=Surface(SurfNum)%OutNormVec
ThWin = AzimWin - PiOvr2
WinNormCrossBase(1) = -SIN(ElevWin)*COS(ThWin)
WinNormCrossBase(2) = SIN(ElevWin)*SIN(ThWin)
WinNormCrossBase(3) = COS(ElevWin)
SunPrime = SUNCOS - WinNormCrossBase*DOT_PRODUCT(SUNCOS,WinNormCrossBase)
ProfileAngVert = ABS(ACOS(DOT_PRODUCT(WinNorm,SunPrime)/SQRT(DOT_PRODUCT(SunPrime,SunPrime))))
END IF
! Constrain to 0 to pi
IF(ProfileAngVert > Pi) ProfileAngVert = 2*Pi - ProfileAngVert
TanProfileAngHor = ABS(TAN(ProfileAngHor))
TanProfileAngVert = ABS(TAN(ProfileAngVert))
NHorDiv = FrameDivider(FrDivNum)%HorDividers
NVertDiv = FrameDivider(FrDivNum)%VertDividers
FrWidth = FrameDivider(FrDivNum)%FrameWidth
DivWidth = FrameDivider(FrDivNum)%DividerWidth
Arealite = (Surface(SurfNum)%Height/(NHorDiv + 1.d0) - DivWidth/2.d0) * &
(Surface(SurfNum)%Width/(NVertDiv + 1.d0) - DivWidth/2.d0)
IF(DivProjOut > 0.0d0 .OR. DivProjIn > 0.0d0) THEN
ArealiteCol = (NHorDiv+1)*Arealite
ArealiteRow = (NVertDiv+1)*Arealite
ELSE
ArealiteCol = GlArea
ArealiteRow = GlArea
END IF
AshVDout = 0.0d0
AshVDin = 0.0d0
AshHDout = 0.0d0
AshHDin = 0.0d0
AshVFout = 0.0d0
AshVFin = 0.0d0
AshHFout = 0.0d0
AshHFin = 0.0d0
AshDDover = 0.0d0
AshFFover = 0.0d0
AshFVDover = 0.0d0
AshFHDover = 0.0d0
IF(DivProjOut > 0.0d0 .OR. DivProjIn > 0.0d0) THEN
! Shaded area from all vertical dividers
AshVDout = NVertDiv * &
MIN((Surface(SurfNum)%Height-NHorDiv*DivWidth)*DivProjOut*TanProfileAngVert,ArealiteCol)
AshVDin = NVertDiv * &
MIN((Surface(SurfNum)%Height-NHorDiv*DivWidth)*DivProjIn*TanProfileAngVert,ArealiteCol)
! Shaded area from all horizontal dividers
AshHDout = NHorDiv * &
MIN((Surface(SurfNum)%Width-NVertDiv*DivWidth)*DivProjOut*TanProfileAngHor,ArealiteRow)
AshHDin = NHorDiv * &
MIN((Surface(SurfNum)%Width-NVertDiv*DivWidth)*DivProjIn*TanProfileAngHor,ArealiteRow)
! Horizontal divider/vertical divider shadow overlap
AshDDover = MIN(DivProjOut*TanProfileAngHor*DivProjOut*TanProfileAngVert,Arealite)*NHorDiv*NVertDiv
END IF
IF(FrProjOut > 0.0d0 .OR. FrProjIn > 0.0d0) THEN
! Shaded area from sides of frame; to avoid complications from possible overlaps between
! shadow from side of frame and shadow from vertical divider the shaded area from side of
! frame is restricted to the area of one column of lites.
AshVFOut = MIN((Surface(SurfNum)%Height-NHorDiv*DivWidth)*FrProjOut*TanProfileAngVert,ArealiteCol)
AshVFin = MIN((Surface(SurfNum)%Height-NHorDiv*DivWidth)*FrProjIn*TanProfileAngVert,ArealiteCol)
! Shaded area from top or bottom of frame; to avoid complications from possible overlaps
! between shadow from top or bottom of frame and shadow from horizontal divider, the shaded
! area from the top or bottom of frame is restricted to the area of one row of lites.
AshHFOut = MIN((Surface(SurfNum)%Width-NVertDiv*DivWidth)*FrProjOut*TanProfileAngHor,ArealiteRow)
AshHFin = MIN((Surface(SurfNum)%Width-NVertDiv*DivWidth)*FrProjIn*TanProfileAngHor,ArealiteRow)
! Top/bottom of frame/side of frame shadow overlap
AshFFover = MIN(FrProjOut*TanProfileAngHor*FrProjOut*TanProfileAngVert,Arealite)
IF(DivProjOut > 0.0d0) THEN
! Frame/vertical divider shadow overlap
AshFVDover = MIN(FrProjOut*DivProjOut*TanProfileAngHor*TanProfileAngVert,Arealite)*NVertDiv
! Frame/horizontal divider shadow overlap
AshFHDover = MIN(FrProjOut*DivProjOut*TanProfileAngHor*TanProfileAngVert,Arealite)*NHorDiv
END IF
END IF
AshFDtotOut = AshVDout + AshHDout + AshVFout + AshHFout - &
(AshDDover + AshFFover + AshFVDover + AshFHDover)
AshFDtotIn = (AshVDin + AshHDin)*FrameDivider(FrDivNum)%DividerSolAbsorp + &
(AshVFin + AshHFin)*FrameDivider(FrDivNum)%FrameSolAbsorp
! Divide by the glazed area of the window
FracShFDout = AshFDtotOut/GlArea
FracShFDin = AshFDtotIn/GlArea
SurfaceWindow(SurfNum)%OutProjSLFracMult(HourNum) = 1.d0-FracShFDout
SurfaceWindow(SurfNum)%InOutProjSLFracMult(HourNum) = 1.d0-(FracShFDin + FracShFDout)
RETURN
END SUBROUTINE CalcFrameDividerShadow