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 | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | ZoneNum | |||
integer, | intent(in) | :: | iRefPoint | |||
integer, | intent(in) | :: | LoopWin | |||
integer, | intent(in) | :: | CalledFrom | |||
real(kind=r64), | intent(in), | DIMENSION(3) | :: | RREF | ||
real(kind=r64), | intent(in), | DIMENSION(3) | :: | VIEWVC | ||
integer, | intent(out) | :: | iWin | |||
integer, | intent(out) | :: | iWin2 | |||
integer, | intent(out) | :: | NWX | |||
integer, | intent(out) | :: | NWY | |||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | W2 | ||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | W3 | ||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | W21 | ||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | W23 | ||
integer, | intent(out) | :: | LSHCAL | |||
integer, | intent(out) | :: | InShelfSurf | |||
integer, | intent(out) | :: | ICtrl | |||
integer, | intent(out) | :: | ShType | |||
integer, | intent(out) | :: | BlNum | |||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | WNORM2 | ||
integer, | intent(out) | :: | ExtWinType | |||
integer, | intent(out) | :: | IConst | |||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | RREF2 | ||
real(kind=r64), | intent(out) | :: | DWX | |||
real(kind=r64), | intent(out) | :: | DWY | |||
real(kind=r64), | intent(out) | :: | DAXY | |||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | U2 | ||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | U23 | ||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | U21 | ||
real(kind=r64), | intent(out), | DIMENSION(3) | :: | VIEWVC2 | ||
logical, | intent(out) | :: | Rectangle | |||
logical, | intent(out) | :: | Triangle | |||
integer, | intent(in), | optional | :: | MapNum | ||
real(kind=r64), | intent(inout), | optional | DIMENSION(:,:) | :: | MapWindowSolidAngAtRefPt | |
real(kind=r64), | intent(inout), | optional | DIMENSION(:,:) | :: | MapWindowSolidAngAtRefPtWtd |
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 FigureDayltgCoeffsAtPointsSetupForWindow(ZoneNum, iRefPoint, LoopWin, CalledFrom, RREF,VIEWVC, iWin, iWin2, &
NWX, NWY, W2,W3,W21, W23, &
LSHCAL,InShelfSurf, &
ICtrl, ShType, BlNum, &
WNORM2, ExtWinType, IConst, RREF2, DWX, DWY, DAXY, U2, U23,U21,VIEWVC2,&
Rectangle, Triangle, &
MapNum, &
MapWindowSolidAngAtRefPt, MapWindowSolidAngAtRefPtWtd)
! SUBROUTINE INFORMATION:
! AUTHOR B. Griffith
! DATE WRITTEN November 2012, refactor from legacy code by Fred Winklemann
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! collect code to setup calculations for each window for daylighting coefficients
! METHODOLOGY EMPLOYED:
! switch as need to serve both reference points and map points based on calledFrom
! REFERENCES:
! na
! USE STATEMENTS:
USE Vectors
USE General, ONLY: POLYF, InterpProfAng, BlindBeamBeamTrans, SafeDivide, RoundSigDigits
USE DaylightingDevices, ONLY: FindTDDPipe
USE DataSystemVariables, ONLY: DetailedSolarTimestepIntegration
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: LoopWin
INTEGER, INTENT(IN) :: ZoneNum
INTEGER, INTENT(IN) :: iRefPoint
INTEGER, INTENT(IN) :: CalledFrom ! indicate which type of routine called this routine
REAL(r64), INTENT(IN), DIMENSION(3) :: RREF ! Location of a reference point in absolute coordinate system
REAL(r64), INTENT(IN), DIMENSION(3) :: VIEWVC ! View vector in absolute coordinate system
INTEGER, INTENT(OUT) :: iWin
INTEGER, INTENT(OUT) :: iWin2
INTEGER, INTENT(OUT) :: NWX
INTEGER, INTENT(OUT) :: NWY
REAL(r64), DIMENSION(3), INTENT(OUT) :: W2 ! Second vertex of window
REAL(r64), DIMENSION(3), INTENT(OUT) :: W3 ! Third vertex of window
REAL(r64), DIMENSION(3), INTENT(OUT) :: W21 ! Vector from window vertex 2 to window vertex 1
REAL(r64), DIMENSION(3), INTENT(OUT) :: W23 ! Vector from window vertex 2 to window vertex 3
INTEGER, INTENT(OUT) :: LSHCAL ! Interior shade calculation flag: 0=not yet calculated, 1=already calculated
INTEGER, INTENT(OUT) :: InShelfSurf ! Inside daylighting shelf surface number
INTEGER, INTENT(OUT) :: ICtrl ! Window control counter
INTEGER, INTENT(OUT) :: ShType ! Window shading type
INTEGER, INTENT(OUT) :: BlNum ! Window blind number
REAL(r64), DIMENSION(3), INTENT(OUT) :: WNORM2 ! Unit vector normal to window
INTEGER , INTENT(OUT) :: ExtWinType ! Exterior window type (InZoneExtWin, AdjZoneExtWin, NotInOrAdjZoneExtWin)
INTEGER, INTENT(OUT) :: IConst ! Construction counter
REAL(r64), DIMENSION(3), INTENT(OUT) :: RREF2 ! Location of virtual reference point in absolute coordinate system
REAL(r64), INTENT(OUT) :: DWX ! Horizontal dimension of window element (m)
REAL(r64), INTENT(OUT) :: DWY ! Vertical dimension of window element (m)
REAL(r64), INTENT(OUT) :: DAXY ! Area of window element
REAL(r64), DIMENSION(3), INTENT(OUT) :: U2 ! Second vertex of window for TDD:DOME (if exists)
REAL(r64), DIMENSION(3), INTENT(OUT) :: U21 ! Vector from window vertex 2 to window vertex 1 for TDD:DOME (if exists)
REAL(r64), DIMENSION(3), INTENT(OUT) :: U23 ! Vector from window vertex 2 to window vertex 3 for TDD:DOME (if exists)
REAL(r64), DIMENSION(3), INTENT(OUT) :: VIEWVC2 ! Virtual view vector in absolute coordinate system
LOGICAL, INTENT(OUT) :: Rectangle ! True if window is rectangular
LOGICAL, INTENT(OUT) :: Triangle ! True if window is triangular
INTEGER, INTENT(IN), OPTIONAL :: MapNum
REAL(r64), DIMENSION(:,:) , INTENT(INOUT), OPTIONAL :: MapWindowSolidAngAtRefPt
REAL(r64), DIMENSION(:,:) , INTENT(INOUT), OPTIONAL :: MapWindowSolidAngAtRefPtWtd
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ZoneNumThisWin ! A window's zone number
INTEGER :: ShelfNum ! Daylighting shelf object number
REAL(r64), DIMENSION(3) :: W1 ! First vertex of window (where vertices are numbered
! counter-clockwise starting at upper left as viewed
! from inside of room
INTEGER :: IConstShaded ! Shaded construction counter
INTEGER :: ScNum ! Window screen number
REAL(r64) :: WW ! Window width (m)
REAL(r64) :: HW ! Window height (m)
REAL(r64), DIMENSION(3) :: WC ! Center point of window
REAL(r64), DIMENSION(3) :: REFWC ! Vector from reference point to center of window
REAL(r64), DIMENSION(3) :: WNORM ! Unit vector normal to window (pointing away from room)
INTEGER :: NDIVX ! Number of window x divisions for daylighting calc
INTEGER :: NDIVY ! Number of window y divisions for daylighting calc
REAL(r64) :: ALF ! Distance from reference point to window plane (m)
REAL(r64), DIMENSION(3) :: W2REF ! Vector from window origin to project of ref. pt. on window plane
REAL(r64) :: D1a ! Projection of vector from window origin to reference
! on window X axis (m)
REAL(r64) :: D1b ! Projection of vector from window origin to reference
! on window Y axis (m)
REAL(r64) :: SolidAngExtWin ! Approx. solid angle subtended by an ext. window wrt ref pt
REAL(r64) :: SolidAngMinIntWin ! Approx. smallest solid angle subtended by an int. window wrt ref pt
REAL(r64) :: SolidAngRatio ! Ratio of SolidAngExtWin and SolidAngMinIntWin
INTEGER :: PipeNum ! TDD pipe object number
REAL(r64), DIMENSION(3) :: REFD ! Vector from ref pt to center of win in TDD:DIFFUSER coord sys (if exists)
REAL(r64), DIMENSION(3) :: VIEWVD ! Virtual view vector in TDD:DIFFUSER coord sys (if exists)
REAL(r64), DIMENSION(3) :: U1 ! First vertex of window for TDD:DOME (if exists)
REAL(r64), DIMENSION(3) :: U3 ! Third vertex of window for TDD:DOME (if exists)
REAL(r64) :: SinCornerAng ! For triangle, sine of corner angle of window element
! Complex fenestration variables
INTEGER :: CplxFenState ! Current complex fenestration state
INTEGER :: NReflSurf ! Number of blocked beams for complex fenestration
INTEGER :: NRefPts ! number of reference points
INTEGER :: WinEl ! Current window element
INTEGER :: ICplxFen ! Complex fenestration counter
INTEGER :: RayIndex
REAL(r64) :: RayVector(3)
REAL(r64) :: TransBeam ! Obstructions transmittance for incoming BSDF rays (temporary variable)
! Complex fenestration variables
CplxFenState = 0
NReflSurf = 0
WinEl = 0
TransBeam = 0.0d0
NRefPts = 0
IWin = ZoneDaylight(ZoneNum)%DayltgExtWinSurfNums(loopwin)
IF (Calledfrom == CalledForRefPoint)THEN
ZoneDaylight(ZoneNum)%SolidAngAtRefPt(iRefPoint,loopwin) = 0.0d0
ZoneDaylight(ZoneNum)%SolidAngAtRefPtWtd(iRefPoint,loopwin) = 0.0d0
ELSEIF (CalledFrom == CalledForMapPoint) THEN
IllumMapCalc(MapNum)%SolidAngAtMapPt(iRefPoint,loopwin) = 0.0d0
IllumMapCalc(MapNum)%SolidAngAtMapPtWtd(iRefPoint,loopwin) = 0.0d0
ENDIF
ZoneNumThisWin = Surface(Surface(IWin)%BaseSurf)%Zone
IF(ZoneNumThisWin == ZoneNum) THEN
ExtWinType = InZoneExtWin
ELSE
ExtWinType = AdjZoneExtWin
END IF
IConst = Surface(IWin)%Construction
IF(SurfaceWindow(IWin)%StormWinFlag == 1) IConst = Surface(IWin)%StormWinConstruction
! TH Added 6/29/2009.
! For thermochromic windows, the daylight and glare factros are calculated for a base window cosntruction
! at base TC layer temperature. During each time step calculations at DayltgInteriorIllum,
! DayltgInteriorMapIllum, and DayltgGlare, the daylight and glare factors are adjusted by the visible
! transmittance ratio = VT of actual TC window based on last hour TC layer temperature / VT of the base TC window
IF (Construct(IConst)%TCFlag == 1) THEN
! For thermochromic windows, use the base window construction at base temperature of the TC layer
IConst = Construct(IConst)%TCMasterConst
ENDIF
ICtrl = Surface(IWin)%WindowShadingControlPtr
ShType = WSC_ST_NoShade ! 'NOSHADE'
BlNum=0
ScNum=0
IF (ICtrl > 0) ShType = WindowShadingControl(ICtrl)%ShadingType
BlNum = SurfaceWindow(IWin)%BlindNumber
ScNum = SurfaceWindow(IWin)%ScreenNumber
ShelfNum = Surface(IWin)%Shelf
IF (ShelfNum > 0) THEN
InShelfSurf = Shelf(Surface(IWin)%Shelf)%InSurf ! Inside daylighting shelf present if > 0
ELSE
InShelfSurf = 0
END IF
Rectangle = .FALSE.
Triangle = .FALSE.
IF (Surface(IWin)%Sides == 3) Triangle = .TRUE.
IF (Surface(IWin)%Sides == 4) Rectangle = .TRUE.
IF (Rectangle) THEN
! Vertices of window (numbered counter-clockwise starting at upper left as viewed
! from inside of room). Assumes original vertices are numbered counter-clockwise from
! upper left as viewed from outside.
W3 = Surface(IWin)%Vertex(2)
W2 = Surface(IWin)%Vertex(3)
W1 = Surface(IWin)%Vertex(4)
ELSE IF (Triangle) THEN
W3 = Surface(IWin)%Vertex(2)
W2 = Surface(IWin)%Vertex(3)
W1 = Surface(IWin)%Vertex(1)
END IF
! Shade/blind calculation flag
LSHCAL = 0
! Visible transmittance at normal incidence
SurfaceWindow(IWin)%VisTransSelected = POLYF(1.0d0,Construct(IConst)%TransVisBeamCoef(1))* &
SurfaceWindow(IWin)%GlazedFrac
! For windows with switchable glazing, ratio of visible transmittance at normal
! incidence for fully switched (dark) state to that of unswitched state
SurfaceWindow(IWin)%VisTransRatio = 1.0d0
IF (ICtrl > 0) THEN
IF (ShType == WSC_ST_SwitchableGlazing) THEN
IConstShaded = Surface(IWin)%ShadedConstruction
SurfaceWindow(IWin)%VisTransRatio = &
SafeDivide(POLYF(1.0d0,Construct(IConstShaded)%TransVisBeamCoef(1)),POLYF(1.0d0,Construct(IConst)%TransVisBeamCoef(1)))
END IF
END IF
! Unit vectors from window vertex 2 to 1 and 2 to 3,
! center point of window, and vector from ref pt to center of window
W21 = W1 - W2
W23 = W3 - W2
HW = SQRT(DOT_PRODUCT(W21,W21))
WW = SQRT(DOT_PRODUCT(W23,W23))
IF (Rectangle) THEN
WC = W2 + (W23 + W21) / 2.d0
ELSE IF (Triangle) THEN
WC = W2 + (W23 + W21) / 3.d0
END IF
SurfaceWindow(IWin)%WinCenter = WC
REFWC = WC - RREF
! Unit vectors
W21 = W21/HW
W23 = W23/WW
! Unit vector normal to window (pointing away from room)
WNORM = Surface(IWin)%lcsz
! Initialize number of window elements
NDIVX = 40
NDIVY = 40
! Distance from ref point to window plane
ALF = ABS(DOT_PRODUCT(WNORM, REFWC))
IF (Calledfrom == CalledForRefPoint)THEN
! Check if ref point to close to window due to input error (0.1524 m below is 0.5 ft)
IF (ALF < 0.1524d0 .AND. ExtWinType == InZoneExtWin) THEN
! Ref pt is close to window plane. Get vector from window
! origin to projection of ref pt on window plane.
W2REF = RREF + ALF * WNORM - W2
D1a = DOT_PRODUCT(W2REF, W23)
D1b = DOT_PRODUCT(W2REF, W21)
! ! Error message if ref pt is too close to window.
IF (D1a > 0.0d0 .and. D1b > 0.0d0 .and. D1b <= HW .and. D1a <= WW) THEN
CALL ShowSevereError('CalcDaylightCoeffRefPoints: Daylighting calculation cannot be done for zone '// &
TRIM(Zone(ZoneNum)%Name)//' because reference point #'// &
TRIM(RoundSigDigits(iRefPoint))//' is less than 0.15m (6") from window plane '//TRIM(Surface(IWin)%Name))
CALL ShowContinueError('Distance=['//TRIM(RoundSigDigits(ALF,5))// &
']. This is too close; check position of reference point.')
CALL ShowFatalError('Program terminates due to preceding condition.')
END IF
ELSE IF (ALF < 0.1524d0 .and. ExtWinType == AdjZoneExtWin) THEN
IF (RefErrIndex(IWin,iRefPoint) == 0) THEN ! only show error message once
CALL ShowWarningError('CalcDaylightCoeffRefPoints: For Zone="'//TRIM(Zone(ZoneNum)%Name)// &
'" External Window="'//TRIM(Surface(IWin)%Name)//'"in Zone="'//TRIM(Zone(Surface(IWin)%Zone)%Name)// &
'" reference point is less than 0.15m (6") from window plane ')
CALL ShowContinueError('Distance=['//trim(RoundSigDigits(ALF,1))//' m] to ref point=['// &
TRIM(RoundSigDigits(RREF(1),1))// &
','//TRIM(RoundSigDigits(RREF(2),1))// &
','//TRIM(RoundSigDigits(RREF(3),1))//'], Inaccuracy in Daylighting Calcs may result.')
RefErrIndex(IWin,iRefPoint)=1
ENDIF
END IF
ELSEIF (CalledFrom == CalledForMapPoint) THEN
IF (ALF < 0.1524d0 .and. ExtWinType == AdjZoneExtWin) THEN
IF (MapErrIndex(IWin,iRefPoint) == 0) THEN ! only show error message once
CALL ShowWarningError('CalcDaylightCoeffMapPoints: For Zone="'//TRIM(Zone(ZoneNum)%Name)// &
'" External Window="'//TRIM(Surface(IWin)%Name)//'"in Zone="'//TRIM(Zone(Surface(IWin)%Zone)%Name)// &
'" map point is less than 0.15m (6") from window plane ')
CALL ShowContinueError('Distance=['//trim(RoundSigDigits(ALF,1))//' m] map point=['// &
TRIM(RoundSigDigits(RREF(1),1))// &
','//TRIM(RoundSigDigits(RREF(2),1))// &
','//TRIM(RoundSigDigits(RREF(3),1))//'], Inaccuracy in Map Calcs may result.')
MapErrIndex(IWin,iRefPoint)=1
ENDIF
END IF
ENDIF
! Number of window elements in X and Y for daylighting calculation
IF (ALF > 0.1524d0) THEN
NDIVX = 1 + INT(4.d0 * WW / ALF)
NDIVY = 1 + INT(4.d0 * HW / ALF)
ENDIF
IF(ExtWinType == AdjZoneExtWin) THEN
! Adjust number of exterior window elements to give acceptable number of rays through
! interior windows in the zone (for accuracy of interior window daylighting calculation)
SolidAngExtWin = SafeDivide( ((Surface(IWin)%Area + SurfaceWindow(IWin)%DividerArea) / Surface(IWin)%Multiplier ), &
ALF**2)
SolidAngMinIntWin = ZoneDaylight(ZoneNum)%MinIntWinSolidAng
SolidAngRatio = MAX(1.0d0,SolidAngExtWin/SolidAngMinIntWin)
NDIVX = SQRT(SolidAngRatio)*NDIVX
NDIVY = SQRT(SolidAngRatio)*NDIVY
END IF
NWX = MIN(40,NDIVX)
NWY = MIN(40,NDIVY)
! Discretization of triangle is simpler if NWX = NWY
IF (Triangle) THEN
NWX = MAX(NWX,NWY)
NWY = NWX
END IF
! Edge lengths of window elements
DWX = WW / NWX
DWY = HW / NWY
! Azimuth and altitude of window normal
SurfaceWindow(IWin)%Phi = ASIN(WNORM(3))
IF (ABS(WNORM(1)) > 1.0d-5 .OR. ABS(WNORM(2)) > 1.0d-5) THEN
SurfaceWindow(IWin)%Theta = ATAN2(WNORM(2), WNORM(1))
ELSE
SurfaceWindow(IWin)%Theta = 0.0d0
END IF
! Recalculation of values for TDD:DOME
IF (SurfaceWindow(IWin)%OriginalClass .EQ. SurfaceClass_TDD_Diffuser) THEN
! Look up the TDD:DOME object
PipeNum = FindTDDPipe(IWin)
IWin2 = TDDPipe(PipeNum)%Dome
! Calculate reference point coords relative to the diffuser coordinate system
! W21, W23, and WNORM are the unit vectors
REFD(1) = DOT_PRODUCT(REFWC,W21)
REFD(2) = DOT_PRODUCT(REFWC,W23)
REFD(3) = DOT_PRODUCT(REFWC,WNORM)
! Calculate view vector coords relative to the diffuser coordinate system
VIEWVD(1) = DOT_PRODUCT(VIEWVC,W21)
VIEWVD(2) = DOT_PRODUCT(VIEWVC,W23)
VIEWVD(3) = DOT_PRODUCT(VIEWVC,WNORM)
U3 = Surface(IWin2)%Vertex(2)
U2 = Surface(IWin2)%Vertex(3)
IF(Surface(IWin2)%Sides == 4) THEN
! Vertices of window (numbered counter-clockwise starting
! at upper left as viewed from inside of room)
! Assumes original vertices are numbered counter-clockwise from
! upper left as viewed from outside.
U3 = Surface(IWin2)%Vertex(2)
U2 = Surface(IWin2)%Vertex(3)
U1 = Surface(IWin2)%Vertex(4)
ELSE IF(Surface(IWin2)%Sides == 3) THEN
U3 = Surface(IWin2)%Vertex(2)
U2 = Surface(IWin2)%Vertex(3)
U1 = Surface(IWin2)%Vertex(1)
END IF
! Unit vectors from window vertex 2 to 1 and 2 to 3,
! center point of window, and vector from ref pt to center of window
U21 = U1 - U2
U23 = U3 - U2
HW = SQRT(DOT_PRODUCT(U21,U21))
WW = SQRT(DOT_PRODUCT(U23,U23))
IF(Surface(IWin2)%Sides == 4) THEN
WC = U2 + (U23 + U21) / 2.d0
ELSE IF(Surface(IWin2)%Sides == 3) THEN
WC = U2 + (U23 + U21) / 3.0d0
END IF
SurfaceWindow(IWin2)%WinCenter = WC
! Unit vectors
U21 = U21 / HW
U23 = U23 / WW
! Unit vector normal to dome (pointing away from TDD)
! These are specific to the exterior.
! NOTE: Preserve WNORM for later in the code.
CALL DayltgCrossProduct(U21, U23, WNORM2)
WNORM2 = WNORM2 / (SQRT(DOT_PRODUCT(WNORM2,WNORM2)))
! Azimuth and altitude of dome normal
! These are specific to the exterior.
SurfaceWindow(IWin2)%Phi = ASIN(WNORM2(3))
IF (ABS(WNORM2(1)) > 1.0d-5 .OR. ABS(WNORM2(2)) > 1.0d-5) THEN
SurfaceWindow(IWin2)%Theta = ATAN2(WNORM2(2), WNORM2(1))
ELSE
SurfaceWindow(IWin2)%Theta = 0.0d0
END IF
! Calculate new virtual reference point coords relative to dome coord system
! W21, W23, and WNORM2 are now the unit vectors for the dome coord system
REFWC = REFD(1) * U21 + REFD(2) * U23 + REFD(3) * WNORM2
RREF2 = WC - REFWC
! Calculate new virtual view vector coords relative to dome coord system
VIEWVC2 = VIEWVD(1) * U21 + VIEWVD(2) * U23 + VIEWVD(3) * WNORM2
! Copy several values from the diffuser so that DayltgInterReflectedIllum works correctly
! These are specific to the interior.
SurfaceWindow(IWin2)%RhoCeilingWall = SurfaceWindow(IWin)%RhoCeilingWall
SurfaceWindow(IWin2)%RhoFloorWall = SurfaceWindow(IWin)%RhoFloorWall
SurfaceWindow(IWin2)%FractionUpgoing = SurfaceWindow(IWin)%FractionUpgoing
SurfaceWindow(IWin2)%GlazedFrac = SurfaceWindow(IWin)%GlazedFrac
ELSE
! This is not a TDD:DIFFUSER. Make sure nothing is messed up for a regular window.
IWin2 = IWin
WNORM2 = WNORM
RREF2 = RREF
VIEWVC2 = VIEWVC
U2 = W2
U21 = W21
U23 = W23
END IF
! Initialize bsdf daylighting coefficients here. Only one time initialization
IF (SurfaceWindow(IWin)%WindowModelType == WindowBSDFModel) THEN
IF (.not. ComplexWind(IWin)%DaylightingInitialized) THEN
if (CalledFrom == CalledForMapPoint) then
NRefPts = IllumMapCalc(MapNum)%TotalMapRefPoints
else if (CalledFrom == CalledForRefPoint) then
NRefPts = ZoneDaylight(ZoneNum)%TotalDaylRefPoints
end if
CALL InitializeCFSDaylighting(ZoneNum, IWin, NWX, NWY, VIEWVC2, RREF, NRefPts, iRefPoint, CalledFrom, MapNum)
!if ((WinEl == (NWX * NWY)).and.(CalledFrom == CalledForMapPoint).and.(NRefPts == iRefPoint)) then
if ((CalledFrom == CalledForMapPoint).and.(NRefPts == iRefPoint)) then
ComplexWind(IWin)%DaylightingInitialized = .TRUE.
end if
END IF
END IF
IF (.NOT. DetailedSolarTimestepIntegration) THEN
! Initialize sky and sun components of direct illuminance (arrays EDIRSK, EDIRSU, EDIRSUdisk)
! and average window luminance (arrays AVWLSK, AVWLSU, AVWLSUdisk), at ref pt.
EDIRSK = 0.d0
EDIRSU = 0.d0
EDIRSUdisk = 0.d0
AVWLSK = 0.d0
AVWLSU = 0.d0
AVWLSUdisk = 0.d0
ELSE
EDIRSK(1:4,1:MaxSlatAngs+1,HourOfDay) = 0.d0
EDIRSU(1:MaxSlatAngs+1,HourOfDay) = 0.d0
EDIRSUdisk(1:MaxSlatAngs+1,HourOfDay) = 0.d0
AVWLSK(1:4,1:MaxSlatAngs+1,HourOfDay) = 0.d0
AVWLSU(1:MaxSlatAngs+1,HourOfDay) = 0.d0
AVWLSUdisk(1:MaxSlatAngs+1,HourOfDay) = 0.d0
ENDIF
IF (Calledfrom == CalledForRefPoint)THEN
! Initialize solid angle subtended by window wrt ref pt
! and solid angle weighted by glare position factor
SurfaceWindow(IWin)%SolidAngAtRefPt(iRefPoint) = 0.0d0
SurfaceWindow(IWin)%SolidAngAtRefPtWtd(iRefPoint) = 0.0d0
ELSEIF (CalledFrom == CalledForMapPoint) THEN
! Initialize solid angle subtended by window wrt ref pt
! and solid angle weighted by glare position factor
MapWindowSolidAngAtRefPt(loopwin,iRefPoint) = 0.0d0
MapWindowSolidAngAtRefPtWtd(loopwin,iRefPoint) = 0.0d0
END IF
! Area of window element
IF (Rectangle) THEN
DAXY = DWX * DWY
ELSE IF (Triangle) THEN
SinCornerAng = SQRT(1.0d0 - DOT_PRODUCT(W21,W23)**2)
DAXY = DWX * DWY * SinCornerAng
END IF
RETURN
END SUBROUTINE FigureDayltgCoeffsAtPointsSetupForWindow