Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | ZoneNum | |||
integer, | intent(in) | :: | iRefPoint | |||
integer, | intent(in) | :: | iHour | |||
integer, | intent(inout) | :: | iSunPos | |||
integer, | intent(in) | :: | iWin | |||
integer, | intent(in) | :: | loopWin | |||
integer, | intent(in) | :: | NWX | |||
integer, | intent(in) | :: | NWY | |||
integer, | intent(in) | :: | ICtrl |
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 FigureRefPointDayltgFactorsToAddIllums(ZoneNum,iRefPoint, iHour, iSunPos, iWin, loopWin, NWX , NWY , ICtrl )
! SUBROUTINE INFORMATION:
! AUTHOR B. Griffith, Oct 2012, derived from legacy code by Fred Winkelmann
! DATE WRITTEN Oct. 2012
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! calculation worker routine to fill daylighting coefficients
! METHODOLOGY EMPLOYED:
! this version is just for reference points.
! REFERENCES:
! na
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ZoneNum
INTEGER, INTENT(IN) :: iRefPoint
INTEGER, INTENT(IN) :: iHour
INTEGER, INTENT(INOUT) :: iSunPos
INTEGER, INTENT(IN) :: iWin
INTEGER, INTENT(IN) :: loopWin
INTEGER, Intent(IN) :: NWX ! Number of window elements in x direction for dayltg calc
INTEGER, Intent(IN) :: NWY ! Number of window elements in y direction for dayltg calc
INTEGER, INTENT(IN) :: ICtrl ! Window control counter
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: tmpDFCalc = 0.05d0 ! cut off illuminance (lux) for exterior horizontal in calculating
! the daylighting and glare factors
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: ISky ! Sky type index: 1=clear, 2=clear turbid, 3=intermediate, 4=overcast
INTEGER :: JSH ! Shading index: J=1 is unshaded window, J=2 is shaded window
REAL(r64) :: VTR ! For switchable glazing, ratio of visible transmittance of
! fully-switched state to that of the unswitched state
IF (SUNCOSHR(3,iHour) < SunIsUpValue) RETURN
ISunPos = ISunPos + 1
! Altitude of sun (degrees)
PHSUN = PHSUNHR(iHour)
SPHSUN = SPHSUNHR(iHour)
CPHSUN = CPHSUNHR(iHour)
! Azimuth of sun in absolute coord sys
THSUN = THSUNHR(iHour)
DO ISKY = 1,4 ! Loop over sky types
! Loop over shading index (1=bare window; 2=diffusing glazing, shade, screen or fixed slat-angle blind;
! 2 to MaxSlatAngs+1 for variable slat-angle blind)
! TH. 9/22/2009. CR 7625 - daylight illuminance spikes during some sunset hours due to the calculated sky and sun
! related daylight factors > 1, which theoretically can occur when sun is perpendicular to the window
! and interior surfaces with high visible reflectance.
! Added tmpDFCalc (default to 0.05 lux) as the cap for GILSK and GILSU in calculating the daylight factors
! the assumption behind it is if exterior horizontal surface does not get daylight, spaces do not get daylight.
DO JSH = 1,MaxSlatAngs+1
IF (.NOT.SurfaceWindow(IWin)%MovableSlats .AND. JSH > 2) EXIT
IF (GILSK(ISKY,iHour) > tmpDFCalc) THEN
ZoneDaylight(ZoneNum)%DaylIllFacSky(loopwin,iRefPoint,ISky,JSH,iHour) = &
(EDIRSK(ISKY,JSH,iHour) + EINTSK(ISKY,JSH,iHour)) / GILSK(ISKY,iHour)
ZoneDaylight(ZoneNum)%DaylSourceFacSky(loopwin,iRefPoint,ISky,JSH,iHour) = &
AVWLSK(ISKY,JSH,iHour) / (NWX*NWY * GILSK(ISKY,iHour))
ZoneDaylight(ZoneNum)%DaylBackFacSky(loopwin,iRefPoint,ISky,JSH,iHour) = &
EINTSK(ISKY,JSH,iHour) * ZoneDaylight(ZoneNum)%AveVisDiffReflect / (PI*GILSK(ISKY,iHour))
ELSE
ZoneDaylight(ZoneNum)%DaylIllFacSky(loopwin,iRefPoint,ISky,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylSourceFacSky(loopwin,iRefPoint,ISky,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylBackFacSky(loopwin,iRefPoint,ISky,JSH,iHour) = 0.d0
ENDIF
IF (ISky == 1) THEN
IF (GILSU(iHour) > tmpDFCalc) THEN
ZoneDaylight(ZoneNum)%DaylIllFacSun(loopwin,iRefPoint,JSH,iHour) = &
(EDIRSU(JSH,iHour) + EINTSU(JSH,iHour)) / (GILSU(iHour) + 0.0001d0)
ZoneDaylight(ZoneNum)%DaylIllFacSunDisk(loopwin,iRefPoint,JSH,iHour) = &
(EDIRSUdisk(JSH,iHour) + EINTSUdisk(JSH,iHour)) / (GILSU(iHour) + 0.0001d0)
ZoneDaylight(ZoneNum)%DaylSourceFacSun(loopwin,iRefPoint,JSH,iHour) = &
AVWLSU(JSH,iHour) / (NWX*NWY * (GILSU(iHour) + 0.0001d0))
ZoneDaylight(ZoneNum)%DaylSourceFacSunDisk(loopwin,iRefPoint,JSH,iHour) = &
AVWLSUdisk(JSH,iHour) / (NWX*NWY * (GILSU(iHour) + 0.0001d0))
ZoneDaylight(ZoneNum)%DaylBackFacSun(loopwin,iRefPoint,JSH,iHour) = &
EINTSU(JSH,iHour) * ZoneDaylight(ZoneNum)%AveVisDiffReflect / (Pi*(GILSU(iHour) + 0.0001d0))
ZoneDaylight(ZoneNum)%DaylBackFacSunDisk(loopwin,iRefPoint,JSH,iHour) = &
EINTSUdisk(JSH,iHour) * ZoneDaylight(ZoneNum)%AveVisDiffReflect / (Pi*(GILSU(iHour) + 0.0001d0))
ELSE
ZoneDaylight(ZoneNum)%DaylIllFacSun(loopwin,iRefPoint,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylIllFacSunDisk(loopwin,iRefPoint,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylSourceFacSun(loopwin,iRefPoint,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylSourceFacSunDisk(loopwin,iRefPoint,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylBackFacSun(loopwin,iRefPoint,JSH,iHour) = 0.d0
ZoneDaylight(ZoneNum)%DaylBackFacSunDisk(loopwin,iRefPoint,JSH,iHour) = 0.d0
ENDIF
END IF
END DO ! End of shading index loop, JSH
! For switchable glazing put daylighting factors for switched (dark) state in IS=2 location
IF (ICtrl > 0) THEN
IF(WindowShadingControl(ICtrl)%ShadingType == WSC_ST_SwitchableGlazing) THEN
VTR = SurfaceWindow(IWin)%VisTransRatio
ZoneDaylight(ZoneNum)%DaylIllFacSky(loopwin,iRefPoint,ISky,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylIllFacSky(loopwin,iRefPoint,ISky,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylSourceFacSky(loopwin,iRefPoint,ISky,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylSourceFacSky(loopwin,iRefPoint,ISky,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylBackFacSky(loopwin,iRefPoint,ISky,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylBackFacSky(loopwin,iRefPoint,ISky,1,iHour)*VTR
IF (ISky == 1) THEN
ZoneDaylight(ZoneNum)%DaylIllFacSun(loopwin,iRefPoint,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylIllFacSun(loopwin,iRefPoint,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylSourceFacSun(loopwin,iRefPoint,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylSourceFacSun(loopwin,iRefPoint,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylBackFacSun(loopwin,iRefPoint,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylBackFacSun(loopwin,iRefPoint,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylIllFacSunDisk(loopwin,iRefPoint,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylIllFacSunDisk(loopwin,iRefPoint,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylSourceFacSunDisk(loopwin,iRefPoint,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylSourceFacSunDisk(loopwin,iRefPoint,1,iHour)*VTR
ZoneDaylight(ZoneNum)%DaylBackFacSunDisk(loopwin,iRefPoint,2,iHour) = &
ZoneDaylight(ZoneNum)%DaylBackFacSunDisk(loopwin,iRefPoint,1,iHour)*VTR
END IF
END IF
END IF ! ICtrl > 0
END DO ! End of sky type loop, ISky
RETURN
END SUBROUTINE FigureRefPointDayltgFactorsToAddIllums