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 FigureBeamSolDiffuseReflFactors(iHour)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann, derived from original CalcBeamSolDiffuseReflFactors
! DATE WRITTEN September 2003
! MODIFIED na
! RE-ENGINEERED B. Griffith, October 2012, revised for timestep integrated solar
! PURPOSE OF THIS SUBROUTINE:
! Calculates factors for irradiance on exterior heat transfer surfaces due to
! beam-to-diffuse solar reflection from obstructions and ground.
! METHODOLOGY EMPLOYED:
! <description>
! REFERENCES:
! na
! USE STATEMENTS:
! na
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:
REAL(r64) :: SunVec(3) =0.0d0 ! Unit vector to sun
INTEGER :: RecSurfNum =0 ! Receiving surface number
INTEGER :: SurfNum =0 ! Heat transfer surface number corresponding to RecSurfNum
INTEGER :: RecPtNum =0 ! Receiving point number
INTEGER :: NumRecPts =0 ! Number of receiving points on a receiving surface
INTEGER :: HitPtSurfNum =0 ! Surface number of hit point: -1 = ground,
! 0 = sky or obstruction with receiving point below ground level,
! >0 = obstruction with receiving point above ground level
REAL(r64) :: ReflBmToDiffSolObs(MaxRecPts) ! Irradiance at a receiving point for
! beam solar diffusely reflected from obstructions, divided by
! beam normal irradiance
REAL(r64) :: ReflBmToDiffSolGnd(MaxRecPts) ! Irradiance at a receiving point for
! beam solar diffusely reflected from the ground, divided by
! beam normal irradiance
INTEGER :: RayNum =0 ! Ray number
INTEGER :: IHit =0 ! > 0 if obstruction is hit; otherwise = 0
REAL(r64) :: OriginThisRay(3) =0.0d0 ! Origin point of a ray (m)
REAL(r64) :: ObsHitPt(3) =0.0d0 ! Hit point on obstruction (m)
INTEGER :: ObsSurfNum =0 ! Obstruction surface number
REAL(r64) :: CosIncBmAtHitPt =0.0d0 ! Cosine of incidence angle of beam solar at hit point
REAL(r64) :: CosIncBmAtHitPt2 =0.0d0 ! Cosine of incidence angle of beam solar at hit point,
! the mirrored shading surface
REAL(r64) :: BmReflSolRadiance =0.0d0 ! Solar radiance at hit point due to incident beam, divided
! by beam normal irradiance
REAL(r64) :: dReflBeamToDiffSol =0.0d0 ! Contribution to reflection factor at a receiving point
! from beam solar reflected from a hit point
REAL(r64) :: SunLitFract =0.0d0 ! Sunlit fraction
ReflBmToDiffSolObs = 0.d0
ReflBmToDiffSolGnd = 0.d0
! Unit vector to sun
SunVec = SunCosHr(1:3,iHour)
! loop through each surface that can receive beam solar reflected as diffuse solar from other surfaces
DO RecSurfNum = 1,TotSolReflRecSurf
SurfNum = SolReflRecSurf(RecSurfNum)%SurfNum
DO RecPtNum = 1, SolReflRecSurf(RecSurfNum)%NumRecPts
ReflBmToDiffSolObs(RecPtNum) = 0.0d0
ReflBmToDiffSolGnd(RecPtNum) = 0.0d0
DO RayNum = 1, SolReflRecSurf(RecSurfNum)%NumReflRays
HitPtSurfNum = SolReflRecSurf(RecSurfNum)%HitPtSurfNum(RecPtNum,RayNum)
! Skip rays that do not hit an obstruction or ground.
! (Note that if a downgoing ray does not hit an obstruction it will have HitPtSurfNum = 0
! if the receiving point is below ground level (see subr. InitSolReflRecSurf); this means
! that a below-ground-level receiving point receives no ground-reflected radiation although
! it is allowed to receive obstruction-reflected solar radiation and direct (unreflected)
! beam and sky solar radiation. As far as reflected solar is concerned, the program does
! not handle a sloped ground plane or a horizontal ground plane whose level is different
! from one side of the building to another.)
IF(HitPtSurfNum == 0) CYCLE ! Ray hits sky or obstruction with receiving pt. below ground level
IF(HitPtSurfNum > 0) THEN
! Skip rays that hit a daylighting shelf, from which solar reflection is calculated separately.
IF(Surface(HitPtSurfNum)%Shelf > 0) CYCLE
! Skip rays that hit a window
! If hit point's surface is a window or glass door go to next ray since it is assumed for now
! that windows have only beam-to-beam, not beam-to-diffuse, reflection
! TH 3/29/2010. Code modified and moved
IF(Surface(HitPtSurfNum)%Class == SurfaceClass_Window .OR. &
Surface(HitPtSurfNum)%Class == SurfaceClass_GLASSDOOR) CYCLE
! Skip rays that hit non-sunlit surface. Assume first time step of the hour.
SunlitFract = SunlitFrac(HitPtSurfNum,iHour,1)
! If hit point's surface is not sunlit go to next ray
! TH 3/25/2010. why limit to HeatTransSurf? shading surfaces should also apply
!IF(Surface(HitPtSurfNum)%HeatTransSurf .AND. SunlitFract < 0.01d0) CYCLE
IF(SunlitFract < 0.01d0) CYCLE
! TH 3/26/2010. If the hit point falls into the shadow even though SunlitFract > 0, can Cycle.
! This cannot be done now, therefore there are follow-up checks of blocking sun ray
! from the hit point.
! TH 3/29/2010. Code modified and moved up
! If hit point's surface is a window go to next ray since it is assumed for now
! that windows have only beam-to-beam, not beam-to-diffuse, reflection
!IF(Surface(HitPtSurfNum)%Construction > 0) THEN
! IF(Construct(Surface(HitPtSurfNum)%Construction)%TypeIsWindow) CYCLE
!END IF
END IF
! Does an obstruction block the vector from this ray's hit point to the sun?
IHit = 0
OriginThisRay = SolReflRecSurf(RecSurfNum)%HitPt(1:3,RecPtNum,RayNum)
! Note: if sun is in back of hit surface relative to receiving point, CosIncBmAtHitPt will be < 0
CosIncBmAtHitPt = DOT_PRODUCT(SolReflRecSurf(RecSurfNum)%HitPtNormVec(1:3,RecPtNum,RayNum),SunVec)
IF(CosIncBmAtHitPt <= 0.0d0) CYCLE
! CR 7872 - TH 4/6/2010. The shading surfaces should point to the receiveing heat transfer surface
! according to the the right hand rule. If user inputs do not follow the rule, use the following
! code to check the mirrored shading surface
IF (HitPtSurfNum >0) THEN
IF (Surface(HitPtSurfNum)%ShadowingSurf) THEN
IF (HitPtSurfNum+1 < TotSurfaces) THEN
IF (Surface(HitPtSurfNum+1)%ShadowingSurf .AND. Surface(HitPtSurfNum+1)%MirroredSurf) THEN
! Check whether the sun is behind the mirrored shading surface
CosIncBmAtHitPt2 = DOT_PRODUCT(Surface(HitPtSurfNum+1)%OutNormVec,SunVec)
IF(CosIncBmAtHitPt2 >= 0.0d0) CYCLE
ENDIF
ENDIF
ENDIF
ENDIF
! TH 3/25/2010. CR 7872. Seems should loop over all possible obstructions for the HitPtSurfNum
! rather than RecSurfNum, because if the HitPtSurfNum is a shading surface,
! it does not belong to SolReflRecSurf which only contain heat transfer surfaces
! that can receive reflected solar (ExtSolar = True)!
! To speed up, ideally should store all possible shading surfaces for the HitPtSurfNum
! obstruction surface in the SolReflSurf(HitPtSurfNum)%PossibleObsSurfNums(loop) array as well
DO ObsSurfNum = 1, TotSurfaces
! DO loop = 1,SolReflRecSurf(RecSurfNum)%NumPossibleObs
! ObsSurfNum = SolReflRecSurf(RecSurfNum)%PossibleObsSurfNums(loop)
!CR 8959 -- The other side of a mirrored surface cannot obstruct the mirrored surface
IF (HitPtSurfNum >0) THEN
IF (Surface(HitPtSurfNum)%MirroredSurf) THEN
IF (ObsSurfNum == HitPtSurfNum-1) CYCLE
END IF
END IF
! skip the hit surface
IF (ObsSurfNum == HitPtSurfNum) CYCLE
! skip mirrored surfaces
IF (Surface(ObsSurfNum)%MirroredSurf) CYCLE
!IF(Surface(ObsSurfNum)%ShadowingSurf .AND. Surface(ObsSurfNum)%Name(1:3) == 'Mir') THEN
! CYCLE
!ENDIF
! skip interior surfaces
IF(Surface(ObsSurfNum)%ExtBoundCond >= 1) CYCLE
! For now it is assumed that obstructions that are shading surfaces are opaque.
! An improvement here would be to allow these to have transmittance.
CALL PierceSurface(ObsSurfNum, OriginThisRay, SunVec, IHit, ObsHitPt)
IF (IHit > 0) EXIT ! An obstruction was hit
END DO
IF(IHit > 0) CYCLE ! Sun does not reach this ray's hit point
! Sun reaches this ray's hit point; get beam-reflected diffuse radiance at hit point for
! unit beam normal solar
!CosIncBmAtHitPt = DOT_PRODUCT(SolReflRecSurf(RecSurfNum)%HitPtNormVec(1:3,RecPtNum,RayNum),SunVec)
! Note: if sun is in back of hit surface relative to receiving point, CosIncBmAtHitPt will be < 0
! and use of MAX in following gives zero beam solar reflecting at hit point.
!BmReflSolRadiance = MAX(0.0d0,CosIncBmAtHitPt)*SolReflRecSurf(RecSurfNum)%HitPtSolRefl(RecPtNum,RayNum)
BmReflSolRadiance = CosIncBmAtHitPt * SolReflRecSurf(RecSurfNum)%HitPtSolRefl(RecPtNum,RayNum)
IF(BmReflSolRadiance > 0.0d0) THEN
! Contribution to reflection factor from this hit point
IF(HitPtSurfNum > 0) THEN
! Ray hits an obstruction
dReflBeamToDiffSol = BmReflSolRadiance * SolReflRecSurf(RecSurfNum)%dOmegaRay(RayNum) * &
SolReflRecSurf(RecSurfNum)%CosIncAngRay(RayNum)/Pi
ReflBmToDiffSolObs(RecPtNum) = ReflBmToDiffSolObs(RecPtNum) + dReflBeamToDiffSol
ELSE
! Ray hits ground (in this case we do not multiply by BmReflSolRadiance since
! ground reflectance and cos of incidence angle of sun on
! ground is taken into account later when ReflFacBmToDiffSolGnd is used)
dReflBeamToDiffSol = SolReflRecSurf(RecSurfNum)%dOmegaRay(RayNum) * &
SolReflRecSurf(RecSurfNum)%CosIncAngRay(RayNum)/Pi
ReflBmToDiffSolGnd(RecPtNum) = ReflBmToDiffSolGnd(RecPtNum) + dReflBeamToDiffSol
END IF
END IF
END DO ! End of loop over rays from receiving point
END DO ! End of loop over receiving points
! Average over receiving points
ReflFacBmToDiffSolObs(SurfNum,iHour) = 0.0d0
ReflFacBmToDiffSolGnd(SurfNum,iHour) = 0.0d0
NumRecPts = SolReflRecSurf(RecSurfNum)%NumRecPts
DO RecPtNum = 1, NumRecPts
ReflFacBmToDiffSolObs(SurfNum,iHour) = ReflFacBmToDiffSolObs(SurfNum,iHour) + ReflBmToDiffSolObs(RecPtNum)
ReflFacBmToDiffSolGnd(SurfNum,iHour) = ReflFacBmToDiffSolGnd(SurfNum,iHour) + ReflBmToDiffSolGnd(RecPtNum)
END DO
ReflFacBmToDiffSolObs(SurfNum,iHour) = ReflFacBmToDiffSolObs(SurfNum,iHour)/NumRecPts
ReflFacBmToDiffSolGnd(SurfNum,iHour) = ReflFacBmToDiffSolGnd(SurfNum,iHour)/NumRecPts
! Do not allow ReflFacBmToDiffSolGnd to exceed the surface's unobstructed ground view factor
ReflFacBmToDiffSolGnd(SurfNum,iHour) = MIN(0.5d0*(1.d0-Surface(SurfNum)%CosTilt), &
ReflFacBmToDiffSolGnd(SurfNum,iHour))
! Note: the above factors are dimensionless; they are equal to
! (W/m2 reflected solar incident on SurfNum)/(W/m2 beam normal solar)
END DO ! End of loop over receiving surfaces
RETURN
END SUBROUTINE FigureBeamSolDiffuseReflFactors