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.
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 AnisoSkyViewFactors
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN April 1999
! MODIFIED LKL; Dec 2002 -- Anisotropic is only sky radiance option
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates view factor multiplier, AnisoSkyMult, for diffuse
! sky irradiance on exterior surfaces taking into account
! anisotropic radiance of the sky. Called by InitSurfaceHeatBalance
!
! In this case the diffuse sky irradiance on a surface is given by
!
! AnisoSkyMult(SurfNum) * DifSolarRad
!
! AnisoSkyMult accounts not only for the sky radiance distribution but
! also for the effects of shading of sky diffuse radiation by
! shadowing surfaces such as overhangs. It does not account for reflection
! of sky diffuse radiation from shadowing surfaces.
!
! Based on an empirical model described in
! R. Perez, P. Ineichen, R. Seals, J. Michalsky and R. Stewart,
! "Modeling Daylight Availability and Irradiance Components from Direct
! and Global Irradiance," Solar Energy 44, 271-289, 1990.
! In this model the radiance of the sky consists of three distributions
! that are superimposed:
! (1) An isotropic distribution that covers the entire sky dome;
! (2) A circumsolar brightening centered around the position of the sun;
! (3) A horizon brightening
!
! The circumsolar brightening is assumed to be concentrated at a point
! source at the center of the sun although this region actually begins at the
! periphery of the solar disk and falls off in intensity with increasing
! angular distance from the periphery.
!
! The horizon brightening is assumed to be concentrated at the horizon and
! to be independent of azimuth. In actuality, for clear skies, the horizon
! brightening is highest at the horizon and decreases in intensity away from
! the horizon. For overcast skies the horizon brightening has a negative value
! since for such skies the sky radiance increases rather than decreases away
! from the horizon.
!
! The F11R, F12R, etc. values were provided by R. Perez, private communication,
! 5/21/99. These values have higher precision than those listed in the above
! paper.
! USE STATEMENTS:
USE DataSystemVariables, ONLY: DetailedSkyDiffuseAlgorithm
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER, DIMENSION(7) :: EpsilonLimit= & ! Upper limit of bins of the sky clearness parameter, Epsilon
(/1.065d0,1.23d0,1.5d0,1.95d0,2.8d0,4.5d0,6.2d0/)
! Circumsolar brightening coefficients; index corresponds to range of Epsilon, the sky clearness parameter
REAL(r64), PARAMETER, DIMENSION(8) :: F11R(8)= &
(/ -0.0083117d0, 0.1299457d0, 0.3296958d0, 0.5682053d0, &
0.8730280d0, 1.1326077d0, 1.0601591d0, 0.6777470d0 /)
REAL(r64), PARAMETER, DIMENSION(8) :: F12R(8)= &
(/ 0.5877285d0, 0.6825954d0, 0.4868735d0, 0.1874525d0, &
-0.3920403d0, -1.2367284d0, -1.5999137d0, -0.3272588d0 /)
REAL(r64), PARAMETER, DIMENSION(8) :: F13R(8)= &
(/ -0.0620636d0, -0.1513752d0, -0.2210958d0, -0.2951290d0, &
-0.3616149d0, -0.4118494d0, -0.3589221d0, -0.2504286d0 /)
! Horizon/zenith brightening coefficient array; index corresponds to range of Epsilon, the sky clearness parameter
REAL(r64), PARAMETER, DIMENSION(8) :: F21R(8)= &
(/ -0.0596012d0, -0.0189325d0, 0.0554140d0, 0.1088631d0, &
0.2255647d0, 0.2877813d0, 0.2642124d0, 0.1561313d0 /)
REAL(r64), PARAMETER, DIMENSION(8) :: F22R(8)= &
(/ 0.0721249d0, 0.0659650d0, -0.0639588d0, -0.1519229d0, &
-0.4620442d0, -0.8230357d0, -1.1272340d0, -1.3765031d0 /)
REAL(r64), PARAMETER, DIMENSION(8) :: F23R(8)= &
(/ -0.0220216d0, -0.0288748d0, -0.0260542d0, -0.0139754d0, &
0.0012448d0, 0.0558651d0, 0.1310694d0, 0.2506212d0 /)
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: CosZenithAng ! Cosine of solar zenith angle
REAL(r64) :: ZenithAng ! Solar zenith angle (radians)
REAL(r64) :: ZenithAngDeg ! Solar zenith angle (degrees)
REAL(r64) :: F1 ! Circumsolar brightening coefficient
REAL(r64) :: F2 ! Horizon/zenith brightening coefficient
REAL(r64) :: Epsilon ! Sky clearness parameter
REAL(r64) :: Delta ! Sky brightness parameter
REAL(r64) :: CosIncAngBeamOnSurface ! Cosine of incidence angle of beam solar on surface
REAL(r64) :: IncAng ! Incidence angle of beam solar on surface (radians)
INTEGER :: SurfNum ! Surface number
INTEGER :: EpsilonBin ! Sky clearness (Epsilon) bin index
REAL(r64) :: AirMass ! Relative air mass
REAL(r64) :: AirMassH ! Intermediate variable for relative air mass calculation
REAL(r64) :: CircumSolarFac ! Ratio of cosine of incidence angle to cosine of zenith angle
REAL(r64) :: KappaZ3 ! Intermediate variable
REAL(r64) :: ViewFactorSkyGeom ! Geometrical sky view factor
! FLOW:
#ifdef EP_Count_Calls
NumAnisoSky_Calls=NumAnisoSky_Calls+1
#endif
CosZenithAng = SOLCOS(3)
ZenithAng = ACOS(CosZenithAng)
ZenithAngDeg = ZenithAng/DegToRadians
AnisoSkyMult = 0.0d0
! Relative air mass
AirMassH = (1.d0 - 0.1d0 * Elevation / 1000.d0)
IF(ZenithAngDeg <= 75.d0) THEN
AirMass = AirMassH/CosZenithAng
ELSE
AirMass = AirMassH/(CosZenithAng + 0.15d0*(93.9d0-ZenithAngDeg)**(-1.253d0))
END IF
KappaZ3 = 1.041d0*ZenithAng**3
Epsilon = ((BeamSolarRad+DifSolarRad)/DifSolarRad + KappaZ3)/(1.0d0+KappaZ3)
Delta = DifSolarRad*AirMass/1353.d0 ! 1353 is average extraterrestrial irradiance (W/m2)
! Circumsolar (F1) and horizon/zenith (F2) brightening coefficients
DO EpsilonBin=1,8
IF(EpsilonBin == 8) EXIT
IF (Epsilon < EpsilonLimit(EpsilonBin)) EXIT
END DO
F1 = MAX(0.d0,F11R(EpsilonBin) + F12R(EpsilonBin)*Delta + F13R(EpsilonBin)*ZenithAng)
F2 = F21R(EpsilonBin) + F22R(EpsilonBin)*Delta + F23R(EpsilonBin)*ZenithAng
DO SurfNum =1,TotSurfaces
IF (.NOT. Surface(SurfNum)%ExtSolar) CYCLE
CosIncAngBeamOnSurface = SOLCOS(1)*Surface(SurfNum)%OutNormVec(1) &
+ SOLCOS(2)*Surface(SurfNum)%OutNormVec(2) &
+ SOLCOS(3)*Surface(SurfNum)%OutNormVec(3)
IncAng = ACOS(CosIncAngBeamOnSurface)
ViewFactorSkyGeom = Surface(SurfNum)%ViewFactorSky
MultIsoSky(SurfNum) = ViewFactorSkyGeom * (1.d0-F1)
! 0.0871557 below corresponds to a zenith angle of 85 deg
CircumSolarFac = MAX(0.d0,CosIncAngBeamOnSurface)/MAX(0.0871557d0,CosZenithAng)
! For near-horizontal roofs, model has an inconsistency that gives sky diffuse
! irradiance significantly different from DifSolarRad when zenith angle is
! above 85 deg. The following forces irradiance to be very close to DifSolarRad
! in this case.
IF(CircumSolarFac > 0.d0 .AND. CosZenithAng < 0.0871557d0 .AND. Surface(SurfNum)%Tilt < 2.0d0) &
CircumSolarFac = 1.d0
MultCircumSolar(SurfNum) = F1*CircumSolarFac
MultHorizonZenith(SurfNum) = F2*Surface(SurfNum)%SinTilt
IF (.not. DetailedSkyDiffuseAlgorithm .or. .not. ShadingTransmittanceVaries .or. &
SolarDistribution == MinimalShadowing) THEN
AnisoSkyMult(SurfNum) = &
MultIsoSky(SurfNum) * DifShdgRatioIsoSky(SurfNum) + &
MultCircumSolar(SurfNum) * SunLitFrac(SurfNum,HourOfDay,TimeStep) + &
MultHorizonZenith(SurfNum) * DifShdgRatioHoriz(SurfNum)
ELSE
AnisoSkyMult(SurfNum) = &
MultIsoSky(SurfNum) * DifShdgRatioIsoSkyHRTS(SurfNum,HourOfDay,TimeStep) + &
MultCircumSolar(SurfNum) * SunLitFrac(SurfNum,HourOfDay,TimeStep) + &
MultHorizonZenith(SurfNum) * DifShdgRatioHorizHRTS(SurfNum,HourOfDay,TimeStep)
curDifShdgRatioIsoSky(SurfNum) = DifShdgRatioIsoSkyHRTS(SurfNum,HourOfDay,TimeStep)
ENDIF
AnisoSkyMult(SurfNum)=MAX(0.0d0,AnisoSkyMult(SurfNum)) ! make sure not negative.
END DO
END SUBROUTINE AnisoSkyViewFactors