Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(out) | :: | GLINDX(2) | |||
integer, | intent(in) | :: | 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 DayltgGlareWithIntWins(GLINDX,ZoneNum)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN March 2004
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculate daylighting glare index for zones with interior windows.
! METHODOLOGY EMPLOYED:
! Finds glare index at reference point IL in a daylit zone using the Cornell/BRS large source
! glare formula. Takes into account inter-reflected illuminance from light entering
! the zone through interior windows
! REFERENCES:
! Based on subroutine DayltgGlare.
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS
INTEGER, INTENT(IN) :: ZoneNum ! Zone number
REAL(r64), INTENT(OUT) :: GLINDX(2) ! Glare index
! SUBROUTINE PARAMETER DEFINITIONS: na
! INTERFACE BLOCK SPECIFICATIONS: na
! DERIVED TYPE DEFINITIONS: na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: IL ! Reference point index: 1=first ref pt, 2=second ref pt
REAL(r64) :: GTOT ! Glare constant
REAL(r64) :: GTOT1 ! Portion of glare constant
REAL(r64) :: GTOT2 ! Portion of glare constant
INTEGER :: IWin ! Window counter
INTEGER :: IS ! Window shading index: 1=unshaded, 2=shaded
REAL(r64) :: BacLum ! Background luminance (cd/m2)
INTEGER :: loop ! Loop index
INTEGER :: RefPoints ! Number of daylighting reference points in zone
! FLOW:
! Initialize glare constant
GTOT = 0.0d0
! Calculate background luminance including effect of inter-reflected illuminance from light
! entering zone through its interior windows
RefPoints = MIN(2,ZoneDaylight(ZoneNum)%TotalDaylRefPoints)
DO IL = 1,RefPoints
BacLum = ZoneDaylight(ZoneNum)%BacLum(IL) + &
ZoneDaylight(ZoneNum)%InterReflIllFrIntWins * ZoneDaylight(ZoneNum)%AveVisDiffReflect / Pi
BacLum = MAX(ZoneDaylight(ZoneNum)%IllumSetPoint(IL)*ZoneDaylight(ZoneNum)%AveVisDiffReflect/Pi,BacLum)
! Loop over exterior windows associated with zone
DO loop = 1,ZoneDaylight(ZoneNum)%NumOfDayltgExtWins
IWin = ZoneDaylight(ZoneNum)%DayltgExtWinSurfNums(loop)
IS = 1
IF((SurfaceWindow(IWin)%ShadingFlag >= 1 .AND. SurfaceWindow(IWin)%ShadingFlag <= 9) .OR. &
SurfaceWindow(IWin)%SolarDiffusing) IS = 2
! Conversion from ft-L to cd/m2, with cd/m2 = 0.2936 ft-L, gives the 0.4794 factor
! below, which is (0.2936)**0.6
GTOT1 = 0.4794d0*(ZoneDaylight(ZoneNum)%SourceLumFromWinAtRefPt(IL,IS,loop)**1.6d0) * &
ZoneDaylight(ZoneNum)%SolidAngAtRefPtWtd(IL,loop)**0.8d0
GTOT2 = BacLum + 0.07d0 * (ZoneDaylight(ZoneNum)%SolidAngAtRefPt(IL,loop)**0.5d0) * &
ZoneDaylight(ZoneNum)%SourceLumFromWinAtRefPt(IL,IS,loop)
GTOT = GTOT + GTOT1 / (GTOT2 + 0.000001d0)
END DO
! Glare index
GLINDX(IL) = 10.0d0*LOG10(GTOT+0.000001d0)
! Set glare index to zero for GTOT < 1
GLINDX(IL) = MAX(0.0d0, GLINDX(IL))
END DO
RETURN
END SUBROUTINE DayltgGlareWithIntWins