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) | :: | iHour |
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 FigureBeamSolSpecularReflFactors(iHour)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN September 2003
! MODIFIED na
! RE-ENGINEERED B. Griffith, October 2012, for timestep integrated solar
! PURPOSE OF THIS SUBROUTINE:
! Calculates factors for beam solar irradiance on exterior heat transfer surfaces due to
! specular (beam-to-beam) reflection from obstructions such as a highly-glazed neighboring
! building. Specular reflection can occur from shading surfaces with non-zero specular
! reflectance and from exterior windows of the building (in calculating reflection from
! these windows, they are assumed to have no shades or blinds).
! Reflection from the ground and opaque building surfaces is assumed to be totally diffuse,
! i.e. these surfaces has no specular reflection component.
! METHODOLOGY EMPLOYED:
! <description>
! REFERENCES:
! na
! USE STATEMENTS:
USE General, ONLY: POLYF
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: iHour
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: loop =0 ! DO loop indices
INTEGER :: loop2 =0 ! DO loop indices
REAL(r64) :: SunVec(3) =0.0d0 ! Unit vector to sun
REAL(r64) :: SunVecMir(3) =0.0d0 ! Unit vector to sun mirrored by a reflecting surface
INTEGER :: RecSurfNum =0 ! Receiving surface number
INTEGER :: SurfNum =0 ! Heat transfer surface number corresponding to RecSurfNum
INTEGER :: NumRecPts =0 ! Number of receiving points on a receiving surface
INTEGER :: RecPtNum =0 ! Receiving point number
REAL(r64) :: RecPt(3) =0.0d0 ! Receiving point (m)
REAL(r64) :: HitPtRefl(3) =0.0d0 ! Hit point on a reflecting surface (m)
REAL(r64) :: ReflBmToDiffSolObs(MaxRecPts) ! Irradiance at a receiving point for
! beam solar diffusely reflected from obstructions, divided by
! beam normal irradiance
!unused INTEGER :: RayNum =0 ! Ray number
INTEGER :: IHitRefl =0 ! > 0 if reflecting surface is hit; otherwise = 0
INTEGER :: IHitObs =0 ! > 0 if obstruction is hit
REAL(r64) :: HitPtObs(3) =0.0d0 ! Hit point on obstruction (m)
INTEGER :: IHitObsRefl =0 ! > 0 if obstruction hit between rec. pt. and reflection point
INTEGER :: ObsSurfNum =0 ! Obstruction surface number
INTEGER :: ReflSurfNum =0 ! Reflecting surface number
INTEGER :: ReflSurfRecNum =0 ! Receiving surface number corresponding to a reflecting surface number
REAL(r64) :: ReflNorm(3) =0.0d0 ! Unit normal to reflecting surface
REAL(r64) :: ReflBmToBmSolObs(MaxRecPts) ! Irradiance at a receiving point for
! beam solar specularly reflected from obstructions, divided by
! beam normal irradiance
REAL(r64) :: ReflDistance =0.0d0 ! Distance from receiving point to hit point on a reflecting surface (m)
REAL(r64) :: ObsDistance =0.0d0 ! Distance from receiving point to hit point on an obstruction (m)
REAL(r64) :: SpecReflectance =0.0d0 ! Specular reflectance of a reflecting surface
INTEGER :: ConstrNumRefl =0 ! Construction number of a reflecting surface
REAL(r64) :: CosIncAngRefl =0.0d0 ! Cosine of incidence angle of beam on reflecting surface
REAL(r64) :: CosIncAngRec =0.0d0 ! Angle of incidence of reflected beam on receiving surface
REAL(r64) :: ReflFac =0.0d0 ! Contribution to specular reflection factor
REAL(r64) :: ReflFacTimesCosIncSum(MaxRecPts) ! Sum of ReflFac times CosIncAngRefl
REAL(r64) :: CosIncWeighted =0.0d0 ! Cosine of incidence angle on receiving surf weighted by reflection factor
ReflBmToDiffSolObs = 0.0d0
ReflFacTimesCosIncSum = 0.0d0
IF(SunCosHr(3,iHour) < SunIsUpValue) RETURN ! Skip if sun is below horizon
! Unit vector to sun
SunVec = SunCosHr(1:3,iHour)
DO RecSurfNum = 1,TotSolReflRecSurf
SurfNum = SolReflRecSurf(RecSurfNum)%SurfNum
IF(SolReflRecSurf(RecSurfNum)%NumPossibleObs > 0) THEN
ReflBmToBmSolObs = 0.0d0
ReflFacTimesCosIncSum = 0.0d0
! Find possible reflecting surfaces for this receiving surface
DO loop = 1, SolReflRecSurf(RecSurfNum)%NumPossibleObs
ReflSurfNum = SolReflRecSurf(RecSurfNum)%PossibleObsSurfNums(loop)
! Keep windows; keep shading surfaces with specular reflectance
IF((Surface(ReflSurfNum)%Class == SurfaceClass_Window .AND. Surface(ReflSurfNum)%ExtSolar) .OR. &
(Surface(ReflSurfNum)%ShadowSurfGlazingFrac > 0.0d0 .AND. &
Surface(ReflSurfNum)%ShadowingSurf)) THEN
! Skip if window and not sunlit
IF(Surface(ReflSurfNum)%Class == SurfaceClass_Window .AND. SunlitFrac(ReflSurfNum,iHour,1) < 0.01d0) CYCLE
! Check if sun is in front of this reflecting surface.
ReflNorm = Surface(ReflSurfNum)%OutNormVec(1:3)
CosIncAngRefl = DOT_PRODUCT(SunVec,ReflNorm)
IF(CosIncAngRefl < 0.0d0) CYCLE
! Get sun position unit vector for mirror image of sun in reflecting surface
SunVecMir = SunVec - 2.0d0*DOT_PRODUCT(SunVec,ReflNorm)*ReflNorm
! Angle of incidence of reflected beam on receiving surface
CosIncAngRec = DOT_PRODUCT(SolReflRecSurf(RecSurfNum)%NormVec,SunVecMir)
IF(CosIncAngRec <= 0.0d0) CYCLE
DO RecPtNum = 1,SolReflRecSurf(RecSurfNum)%NumRecPts
! See if ray from receiving point to mirrored sun hits the reflecting surface
RecPt = SolReflRecSurf(RecSurfNum)%RecPt(1:3,RecPtNum)
CALL PierceSurface(ReflSurfNum, RecPt, SunVecMir, IHitRefl, HitPtRefl)
IF(IHitRefl > 0) THEN
! Reflecting surface was hit
ReflDistance = SQRT(DOT_PRODUCT(HitPtRefl-RecPt,HitPtRefl-RecPt))
! Determine if ray from receiving point to hit point is obstructed
IHitObsRefl = 0
DO loop2 = 1,SolReflRecSurf(RecSurfNum)%NumPossibleObs
ObsSurfNum = SolReflRecSurf(RecSurfNum)%PossibleObsSurfNums(loop2)
IF(ObsSurfNum == ReflSurfNum .OR. ObsSurfNum == Surface(ReflSurfNum)%BaseSurf) CYCLE
CALL PierceSurface(ObsSurfNum,RecPt,SunVecMir,IHitObs,HitPtObs)
IF(IHitObs > 0) THEN
ObsDistance = SQRT(DOT_PRODUCT(HitPtObs-RecPt,HitPtObs-RecPt))
IF(ObsDistance < ReflDistance) THEN
IHitObsRefl = 1
EXIT
END IF
END IF
END DO
IF(IHitObsRefl > 0) CYCLE ! Obstruct'n closer than reflect'n pt. was hit; go to next rec. pt.
! There is no obstruction for this ray between rec. pt. and hit point on reflecting surface.
! See if ray from hit pt. on reflecting surface to original (unmirrored) sun position is obstructed
IHitObs = 0
IF(Surface(ReflSurfNum)%Class == SurfaceClass_Window) THEN
! Reflecting surface is a window.
! Receiving surface number for this window.
ReflSurfRecNum = Surface(ReflSurfNum)%ShadowSurfRecSurfNum
IF(ReflSurfRecNum > 0) THEN
! Loop over possible obstructions for this window
DO loop2 = 1,SolReflRecSurf(ReflSurfRecNum)%NumPossibleObs
ObsSurfNum = SolReflRecSurf(ReflSurfRecNum)%PossibleObsSurfNums(loop2)
CALL PierceSurface(ObsSurfNum,HitPtRefl,SunVec,IHitObs,HitPtObs)
IF(IHitObs > 0) EXIT
END DO
END IF
ELSE
! Reflecting surface is a building shade
DO ObsSurfNum = 1, TotSurfaces
IF(.NOT.Surface(ObsSurfNum)%ShadowSurfPossibleObstruction) CYCLE
IF(ObsSurfNum == ReflSurfNum) CYCLE
!TH2 CR8959 -- Skip mirrored surfaces
IF(Surface(ObsSurfNum)%MirroredSurf) CYCLE
!TH2 CR8959 -- The other side of a mirrored surface cannot obstruct the mirrored surface
IF (Surface(ReflSurfNum)%MirroredSurf) THEN
IF (ObsSurfNum == ReflSurfNum-1) CYCLE
END IF
CALL PierceSurface(ObsSurfNum,HitPtRefl,SunVec,IHitObs,HitPtObs)
IF(IHitObs > 0) EXIT
END DO
END IF
IF(IHitObs > 0) CYCLE ! Obstruct'n hit between reflect'n hit point and sun; go to next receiving pt.
! No obstructions. Calculate reflected beam irradiance at receiving pt. from this reflecting surface.
SpecReflectance = 0.0d0
IF(Surface(ReflSurfNum)%Class == SurfaceClass_Window) THEN
ConstrNumRefl = Surface(ReflSurfNum)%Construction
SpecReflectance = POLYF(ABS(CosIncAngRefl),Construct(ConstrNumRefl)%ReflSolBeamFrontCoef(1:6))
END IF
IF(Surface(ReflSurfNum)%ShadowingSurf.AND.Surface(ReflSurfNum)%ShadowSurfGlazingConstruct > 0) THEN
ConstrNumRefl = Surface(ReflSurfNum)%ShadowSurfGlazingConstruct
SpecReflectance = Surface(ReflSurfNum)%ShadowSurfGlazingFrac * &
POLYF(ABS(CosIncAngRefl),Construct(ConstrNumRefl)%ReflSolBeamFrontCoef(1:6))
ENDIF
! Angle of incidence of reflected beam on receiving surface
CosIncAngRec = DOT_PRODUCT(SolReflRecSurf(RecSurfNum)%NormVec,SunVecMir)
ReflFac = SpecReflectance * CosIncAngRec
! Contribution to specular reflection factor
ReflBmToBmSolObs(RecPtNum) = ReflBmToBmSolObs(RecPtNum) + ReflFac
ReflFacTimesCosIncSum(RecPtNum) = ReflFacTimesCosIncSum(RecPtNum) + ReflFac*CosIncAngRec
END IF ! End of check if reflecting surface was hit
END DO ! End of loop over receiving points
END IF ! End of check if valid reflecting surface
END DO ! End of loop over obstructing surfaces
! Average over receiving points
NumRecPts = SolReflRecSurf(RecSurfNum)%NumRecPts
DO RecPtNum = 1,NumRecPts
IF (ReflBmToBmSolObs(RecPtNum) /= 0.0d0) THEN
CosIncWeighted = ReflFacTimesCosIncSum(RecPtNum) / ReflBmToBmSolObs(RecPtNum)
ELSE
CosIncWeighted = 0.0d0
ENDIF
CosIncAveBmToBmSolObs(SurfNum,iHour) = CosIncAveBmToBmSolObs(SurfNum,iHour) + CosIncWeighted
ReflFacBmToBmSolObs(SurfNum,iHour) = ReflFacBmToBmSolObs(SurfNum,iHour) + ReflBmToBmSolObs(RecPtNum)
END DO
ReflFacBmToBmSolObs(SurfNum,iHour) = ReflFacBmToBmSolObs(SurfNum,iHour) / REAL(NumRecPts,r64)
CosIncAveBmToBmSolObs(SurfNum,iHour) = CosIncAveBmToBmSolObs(SurfNum,iHour) / REAL(NumRecPts,r64)
END IF ! End of check if number of possible obstructions > 0
END DO ! End of loop over receiving surfaces
RETURN
END SUBROUTINE FigureBeamSolSpecularReflFactors