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) | :: | ISurf | |||
integer, | intent(in) | :: | IState | |||
type(BSDFWindowGeomDescr), | intent(inout) | :: | Window | |||
type(BSDFGeomDescr), | intent(inout) | :: | Geom | |||
type(BSDFStateDescr), | intent(inout) | :: | State |
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 CFSShadeAndBeamInitialization(iSurf, iState, Window, Geom, State)
! SUBROUTINE INFORMATION:
! AUTHOR Simon Vidanovic
! DATE WRITTEN May 2013
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates shading properties of complex fenestration
! Refactoring from Klems code
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE vectors
USE DataGlobals, ONLY: HourOfDay, TimeStep, KickoffSizing, KickoffSimulation
USE DataSystemVariables, ONLY: DetailedSolarTimestepIntegration
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ISurf !Window surface number
INTEGER, INTENT(IN) :: IState !Window state number
TYPE (BSDFWindowGeomDescr),INTENT(INOUT) :: Window !Window Geometry
TYPE (BSDFGeomDescr), INTENT(INOUT) :: Geom !State Geometry
TYPE (BSDFStateDescr), INTENT(INOUT) :: State !State Description
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
TYPE (vector) :: SunDir =vector(0.0d0, 0.0d0, 1.0d0) !unit vector pointing toward sun (world CS)
TYPE (vector) :: Posit =vector(0.0d0, 0.0d0, 1.0d0) !vector location of current ground point
TYPE (vector) :: HitPt =vector(0.0d0, 0.0d0, 1.0d0) !vector location of ray intersection with a surface
REAL(r64) :: DotProd =0.0d0 !temporary variable for testing dot products
INTEGER :: I !general purpose index
INTEGER :: IncRay !Index of incident ray corresponding to beam direction
REAL(r64) :: Theta !Theta angle of incident ray correspongind to beam direction
REAL(r64) :: Phi !Phi angle of incident ray correspongind to beam direction
INTEGER :: IHit =0 !hit flag
INTEGER :: J !general purpose index
INTEGER :: JSurf !general purpose surface number
INTEGER :: K !general purpose index
INTEGER :: Hour !hour of day
INTEGER :: TotHits !hit counter
INTEGER :: TS !time step
IF (KickoffSizing .or. KickoffSimulation) RETURN
IF (.NOT. DetailedSolarTimestepIntegration) THEN
DO Hour =1 , 24
DO TS = 1, NumOfTimeStepInHour
SunDir = SUNCOSTS(1:3,Hour,TS)
Theta = 0.0d0
Phi = 0.0d0
IF (SUNCOSTS(3 ,Hour, TS) > SunIsUpValue) THEN
IncRay = FindInBasis(SunDir, Front_Incident, ISurf, IState, ComplexWind(ISurf)%Geom(IState)%Inc, Theta, Phi)
ComplexWind(ISurf)%Geom(IState)%ThetaBm(Hour,TS) = Theta
ComplexWind(ISurf)%Geom(IState)%PhiBm(Hour,TS) = Phi
ELSE
ComplexWind(ISurf)%Geom(IState)%ThetaBm(Hour,TS) = 0.0d0
ComplexWind(ISurf)%Geom(IState)%PhiBm(Hour,TS) = 0.0d0
IncRay = 0 !sundown can't have ray incident on window
ENDIF
IF (IncRay > 0 ) THEN
!Sun may be incident on the window
ComplexWind(ISurf)%Geom(IState)%SolBmIndex(Hour,TS) = IncRay
ELSE
!Window can't be sunlit, set front incidence ray index to zero
ComplexWind(ISurf)%Geom(IState)%SolBmIndex(Hour,TS) = 0
ENDIF
DO I = 1, ComplexWind(ISurf)%Geom(IState)%NGnd !Gnd pt loop
IHit = 0
TotHits = 0
DO JSurf = 1, TotSurfaces
! the following test will cycle on anything except exterior surfaces and shading surfaces
IF( Surface(JSurf)%HeatTransSurf.AND.Surface(JSurf)%ExtBoundCond /= ExternalEnvironment) CYCLE
! skip surfaces that face away from the ground point
DotProd = SunDir .dot. Surface(JSurf)%NewellSurfaceNormalVector
IF (DotProd >= 0.0d0) CYCLE
!Looking for surfaces between GndPt and sun
CALL PierceSurfaceVector(JSurf, ComplexWind(ISurf)%Geom(IState)%GndPt(I), SunDir, IHit, HitPt)
IF (IHit == 0) CYCLE
! Are not going into the details of whether a hit surface is transparent
! Since this is ultimately simply weighting the transmittance, so great
! detail is not warranted
TotHits = TotHits + 1
EXIT
END DO
IF (TotHits > 0) THEN
ComplexWind(ISurf)%Geom(IState)%SolBmGndWt(I ,Hour, TS) = 0.0d0
ELSE
ComplexWind(ISurf)%Geom(IState)%SolBmGndWt(I ,Hour, TS) = 1.0d0
ENDIF
END DO ! Gnd pt loop
! update window beam properties
CALL CalculateWindowBeamProperties(ISurf, IState, ComplexWind(ISurf), &
ComplexWind(ISurf)%Geom(IState), SurfaceWindow(ISurf)%ComplexFen%State(IState), Hour, TS)
END DO ! Timestep loop
END DO ! Hour loop
ELSE ! detailed timestep integration
SunDir = SUNCOSTS(1:3, HourOfDay, TimeStep)
Theta = 0.0d0
Phi = 0.0d0
IF (SUNCOSTS(3 , HourOfDay, TimeStep ) > SunIsUpValue) THEN
IncRay = FindInBasis ( SunDir, Front_Incident, ISurf, IState, ComplexWind(ISurf)%Geom(IState)%Inc, Theta, Phi)
ComplexWind(ISurf)%Geom(IState)%ThetaBm(HourOfDay,TimeStep) = Theta
ComplexWind(ISurf)%Geom(IState)%PhiBm(HourOfDay,TimeStep) = Phi
ELSE
ComplexWind(ISurf)%Geom(IState)%ThetaBm(HourOfDay,TimeStep) = 0.0d0
ComplexWind(ISurf)%Geom(IState)%PhiBm(HourOfDay,TimeStep) = 0.0d0
IncRay = 0 !sundown can't have ray incident on window
ENDIF
IF (IncRay > 0) THEN
!Sun may be incident on the window
ComplexWind(ISurf)%Geom(IState)%SolBmIndex(HourOfDay,TimeStep) = IncRay
ELSE
!Window can't be sunlit, set front incidence ray index to zero
ComplexWind(ISurf)%Geom(IState)%SolBmIndex(HourOfDay,TimeStep) = 0.0d0
ENDIF
DO I = 1 ,ComplexWind(ISurf)%Geom(IState)%NGnd !Gnd pt loop
IHit = 0
TotHits = 0
DO JSurf = 1, TotSurfaces
! the following test will cycle on anything except exterior surfaces and shading surfaces
IF(Surface(JSurf)%HeatTransSurf.AND.Surface(JSurf)%ExtBoundCond /= ExternalEnvironment) CYCLE
! skip surfaces that face away from the ground point
DotProd = SunDir.dot.Surface(JSurf)%NewellSurfaceNormalVector
IF (DotProd >= 0.0d0 ) CYCLE
!Looking for surfaces between GndPt and sun
CALL PierceSurfaceVector(JSurf, ComplexWind(ISurf)%Geom(IState)%GndPt(I), SunDir, IHit, HitPt)
IF (IHit == 0) CYCLE
! Are not going into the details of whether a hit surface is transparent
! Since this is ultimately simply weighting the transmittance, so great
! detail is not warranted
TotHits = TotHits + 1
EXIT
END DO
IF (TotHits > 0) THEN
ComplexWind(ISurf)%Geom(IState)%SolBmGndWt (I, HourOfDay, TimeStep) = 0.0d0
ELSE
ComplexWind(ISurf)%Geom(IState)%SolBmGndWt (I, HourOfDay, TimeStep) = 1.0d0
ENDIF
END DO ! Gnd pt loop
! Update window beam properties
CALL CalculateWindowBeamProperties(ISurf, IState, ComplexWind(ISurf),&
ComplexWind(ISurf)%Geom(IState), SurfaceWindow( ISurf )%ComplexFen%State(IState), HourOfDay, TimeStep)
ENDIF ! solar calculation mode, average over days or detailed
RETURN
END SUBROUTINE CFSShadeAndBeamInitialization