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 CalcWindowStaticProperties(ISurf, IState, Window, Geom, State)
! SUBROUTINE INFORMATION:
! AUTHOR Joe Klems
! DATE WRITTEN <date_written>
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Calculates those optical properties of all the Complex Fenestrations that
! do not depend on the beam direction (hence, on hour and time step)
! METHODOLOGY EMPLOYED:
! <description>
! REFERENCES:
! na
! USE STATEMENTS:
USE vectors
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: ISurf !Surface number of the complex fenestration
INTEGER, INTENT(IN) :: IState !State number of the complex fenestration state
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:
INTEGER :: IConst !Pointer to construction for this fenestration
INTEGER :: I =0 !general purpose index
INTEGER :: J =0 !general purpose index
INTEGER :: JJ =0 !general purpose index--ray
INTEGER :: L =0 !general purpose index--layer
INTEGER :: M =0 !general purpose index--ray
INTEGER :: KBkSurf !back surface index
INTEGER :: JSurf !surface number (used for back surface)
INTEGER :: BaseSurf !base surface number (used for finding back surface)
REAL(r64) :: Sum1 !general purpose temporary sum
REAL(r64) :: Sum2 !general purpose temporary sum
REAL(r64) :: Sum3 !general purpose temporary sum
REAL(r64) :: Hold !temp variable
IConst = SurfaceWindow(ISurf)%ComplexFen%State(IState)%Konst
!Calculate the hemispherical-hemispherical transmittance
Sum1 = 0.0d0
Sum2 = 0.0d0
DO J = 1, Geom%Inc%NBasis !Incident ray loop
Sum2 = Sum2 + Geom%Inc%Lamda (J)
DO M = 1 , Geom%Trn%NBasis !Outgoing ray loop
Sum1 =Sum1 + Geom%Inc%Lamda(J) * Geom%Trn%Lamda(M) * Construct(IConst)%BSDFInput%SolFrtTrans (J, M)
END DO !Outgoing ray loop
END DO !Incident ray loop
IF (Sum2 > 0 ) THEN
State%WinDiffTrans = Sum1/Sum2
ELSE
State%WinDiffTrans = 0.0d0
CALL ShowWarningError ('BSDF--Inc basis has zero projected solid angle')
ENDIF
!Calculate the hemispherical-hemispherical transmittance for visible spetrum
Sum1 = 0.0d0
Sum2 = 0.0d0
DO J = 1 , Geom%Inc%NBasis !Incident ray loop
Sum2 = Sum2 + Geom%Inc%Lamda(J)
DO M = 1, Geom%Trn%NBasis !Outgoing ray loop
Sum1 =Sum1 + Geom%Inc%Lamda(J) * Geom%Trn%Lamda(M) * Construct(IConst)%BSDFInput%VisFrtTrans (J, M)
END DO !Outgoing ray loop
END DO !Incident ray loop
IF (Sum2 > 0.0d0 ) THEN
State%WinDiffVisTrans = Sum1/Sum2
ELSE
State%WinDiffVisTrans = 0.0d0
CALL ShowWarningError ('BSDF--Inc basis has zero projected solid angle')
ENDIF
!Set the nominal diffuse transmittance so the surface isn't mistaken as opaque
Construct(IConst)%TransDiff = SurfaceWindow(ISurf)%ComplexFen%State(IState)%WinDiffTrans
!Calculate Window Sky Transmittance (transmitted radiation assumed diffuse)
!and Sky Absorptance (by layer)
Sum1 = 0.0d0
Sum2 = 0.0d0
Sum3 = 0.0d0
DO JJ = 1 , Geom%NSky
DO M = 1 , Geom%Trn%NBasis
J = Geom%SkyIndex( JJ )
Sum1 = Sum1 + Geom%SolSkyWt(JJ) * Construct(IConst)%BSDFInput%SolFrtTrans(J, M) * Geom%Inc%Lamda(J) * Geom%Trn%Lamda(M)
END DO
END DO
DO JJ = 1 , Geom%NSky
J = Geom%SkyIndex( JJ )
Sum2 = Sum2 + Geom%SolSkyWt ( JJ ) * Geom%Inc%Lamda( J )
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinSkyTrans = Sum1/Sum2
ELSE
State%WinSkyTrans = 0.0d0
END IF
ALLOCATE(State%WinSkyFtAbs(State%NLayers))
!Also allocate the beam quantities for this state
DO L = 1 , State%NLayers
Sum3 = 0.0d0
DO JJ = 1, Geom%NSky
J = Geom%SkyIndex( JJ )
Sum3 = Sum3 + Geom%SolSkyWt (JJ) * Geom%Inc%Lamda(J) * Construct(IConst)%BSDFInput%Layer(L)%FrtAbs(1 ,J)
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinSkyFtAbs(L) = Sum3/Sum2
ELSE
State%WinSkyFtAbs(L) = 0.0d0
END IF
END DO
!Calculate Window Sky/Ground Transmittance
!(applies to ground-reflected sky radiation, transmitted radiation assumed diffuse)
!This is the same calculation as the sky transmittance, except that the set of incident
!rays and the ray weights are different
!Also calculate Window Sky/Ground Absorptance (by layer)
Sum1 = 0.0d0
Sum2 = 0.0d0
Sum3 = 0.0d0
DO JJ = 1, Geom%NGnd
DO M = 1 , Geom%Trn%NBasis
J = Geom%GndIndex(JJ)
Sum1 = Sum1 + Geom%SolSkyGndWt(JJ) * Construct(IConst)%BSDFInput%SolFrtTrans(J, M) * Geom%Inc%Lamda(J) * Geom%Trn%Lamda(M)
END DO
END DO
DO JJ = 1 , Geom%NGnd
J = Geom%GndIndex(JJ)
Sum2 = Sum2 + Geom%SolSkyGndWt ( JJ ) * Geom%Inc%Lamda( J )
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinSkyGndTrans = Sum1/Sum2
ELSE
State%WinSkyGndTrans = 0.0d0
END IF
ALLOCATE(State%WinSkyGndAbs(State%NLayers))
DO L = 1 , State%NLayers
Sum3 = 0.0d0
DO JJ = 1, Geom%NGnd
J = Geom%GndIndex( JJ )
Sum3 = Sum3 + Geom%SolSkyGndWt(JJ) * Geom%Inc%Lamda(J) * Construct(IConst)%BSDFInput%Layer(L)%FrtAbs(1, J)
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinSkyGndAbs(L) = Sum3/Sum2
ELSE
State%WinSkyGndAbs(L) = 0.0d0
END IF
END DO
!Calculate Window Back Hemispherical Reflectance and Layer Back Hemispherical Absorptance
Sum1 = 0.0d0
Sum2 = 0.0d0
Sum3 = 0.0d0
!Note this again assumes the equivalence Inc basis = transmission basis for back incidence and
! Trn basis = incident basis for back incidence
DO J = 1, Geom%Trn%NBasis
DO M = 1, Geom%Inc%NBasis
Sum1 = Sum1 + Construct(IConst)%BSDFInput%SolBkRefl(J, M) * Geom%Trn%Lamda(J) * Geom%Inc%Lamda(M)
END DO
END DO
DO J = 1 , Geom%Trn%NBasis
Sum2 = Sum2 + Geom%Trn%Lamda( J )
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinBkHemRefl = Sum1/Sum2
ELSE
State%WinBkHemRefl = 0.0d0
END IF
Construct(IConst)%ReflectSolDiffBack = State%WinBkHemRefl
ALLOCATE(State%WinBkHemAbs(State%NLayers))
DO L = 1, State%NLayers
DO J = 1, Geom%Trn%NBasis
Sum3 = Sum3 + Geom%Trn%Lamda(J) * Construct(IConst)%BSDFInput%Layer(L)%BkAbs(1, J)
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinBkHemAbs(L) = Sum3/Sum2
ELSE
State%WinBkHemAbs(L) = 0.0d0
END IF
!Put this into the construction for use in non-detailed optical calculations
Construct(IConst)%AbsDiffBack(L) = State%WinBkHemAbs(L)
END DO
!Calculate Window Layer Front Hemispherical Absorptance
Sum1 = 0.0d0
Sum2 = 0.0d0
DO J = 1, Geom%Inc%NBasis
Sum2 = Sum2 + Geom%Inc%Lamda(J)
END DO
ALLOCATE(State%WinFtHemAbs(State%NLayers))
DO L = 1, State%NLayers
Sum1 = 0.0d0
DO J = 1 , Geom%Inc%NBasis
Sum1 = Sum1 + Geom%Inc%Lamda( J ) * Construct(IConst)%BSDFInput%Layer(L)%FrtAbs(1, J)
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinFtHemAbs(L) = Sum1/Sum2
ELSE
State%WinFtHemAbs(L) = 0.0d0
END IF
!Put this into the construction for use in non-detailed optical calculations
Construct(IConst)%AbsDiff(L) = State%WinFtHemAbs(L)
END DO
!Calculate Window Back Hemispherical Visible Reflectance
Sum1 = 0.0d0
Sum2 = 0.0d0
!Note this again assumes the equivalence Inc basis = transmission basis for back incidence and
! Trn basis = incident basis for back incidence
DO J = 1, Geom%Trn%NBasis
DO M = 1, Geom%Inc%NBasis
Sum1 = Sum1 + Construct(IConst)%BSDFInput%VisBkRefl(J, M) * Geom%Trn%Lamda(J) * Geom%Inc%Lamda(M)
END DO
END DO
DO J = 1 , Geom%Trn%NBasis
Sum2 = Sum2 + Geom%Trn%Lamda( J )
END DO
IF (Sum2 /= 0.0d0) THEN
State%WinBkHemVisRefl = Sum1/Sum2
ELSE
State%WinBkHemVisRefl = 0.0d0
END IF
Construct(IConst)%ReflectVisDiffBack = State%WinBkHemVisRefl
! * * * *
!Note potential problem if one relaxes the assumption that Inc and Trn basis have same structure:
! The following calculations are made for the set of ray numbers defined in the Trn basis that
! were determined to connect the center of the window to a particular back surface.
! Here it is assumed that one can reverse these rays and get an equivalent set in the Trn
! basis for back-incidence quantities: back transmittance and back layer absorptance
! This assumption may fail if the Inc and Trn bases are allowed to have different structure.
! Note also that in this case one would need to rethink the relationship of the basis
! definitions to back-incidence quantities: possibly this would
! also require that the basis for back incident quantities be
! different from the Trn basis, and similarly the basis for backward outgoing rays
! be different from the Inc basis.
! * * * *
! Note that we are assuming that for back incidence the layer numberings are the same
! as for front incidence, i.e., from outside to inside when incidence is from inside
! * * * *
!For back surfaces that are complex fenestrations, calculate the directional-hemispherical back
! reflectance and the directional back absorptance by layer for this fenestration receiving
! radiation via the back surface
! Make this calculation only for cases where the back surface is a Complex Fenestration
!
!First allocate the back surface section of the state properties
IF(.NOT.ALLOCATED(State%BkSurf)) ALLOCATE(State%BkSurf(Window%NBkSurf))
DO KBkSurf = 1, Window%NBkSurf !back surface loop
BaseSurf = Surface(ISurf)%BaseSurf !ShadowComb is organized by base surface
JSurf = ShadowComb(BaseSurf)%BackSurf(KBkSurf)
IF ( SurfaceWindow(JSurf)%WindowModelType /= WindowBSDFModel ) CYCLE
! Directional-hemispherical back reflectance
Sum1 = 0.0d0
Sum2 = 0.0d0
DO J = 1, Geom%NSurfInt(KBkSurf) !Inc Ray loop
Sum2 = Sum2 + Geom%Trn%Lamda( Geom%SurfInt(KBkSurf , J ) )
DO M = 1, Geom%Inc%NBasis !Outgoing Ray loop
Sum1 = Sum1 + Geom%Trn%Lamda(Geom%SurfInt(KBkSurf, J)) * Geom%Inc%Lamda(M) * &
Construct(IConst)%BSDFInput%SolBkRefl(M, Geom%SurfInt(KBkSurf, J))
END DO !Outgoing Ray loop
END DO !Inc Ray loop
IF (Sum2 > 0.0d0 ) THEN
Hold =Sum1/Sum2
DO I = 1, 24
DO J = 1 ,NumOfTimeStepInHour
State%BkSurf(KBkSurf)%WinDHBkRefl( I , J ) = Hold
END DO
END DO
ELSE
DO I = 1 ,24
DO J = 1 ,NumOfTimeStepInHour
State%BkSurf(KBkSurf)%WinDHBkRefl(I, J) = 0.0d0
END DO
END DO
ENDIF
! Directional layer back absorption
DO L = 1, State%NLayers !layer loop
Sum1 = 0.0d0
Sum2 = 0.0d0
DO J = 1, Geom%NSurfInt(KBkSurf) !Inc Ray loop
Sum2 = Sum2 + Geom%Trn%Lamda(Geom%SurfInt(KBkSurf, J))
Sum1 = Sum1 + Geom%Trn%Lamda(Geom%SurfInt(KBkSurf , J)) * &
Construct(IConst)%BSDFInput%Layer(L)%BkAbs (1, Geom%SurfInt(KBkSurf, J))
END DO !Inc Ray loop
IF (Sum2 > 0.0d0 ) THEN
Hold =Sum1/Sum2
DO I = 1, 24
DO J = 1, NumOfTimeStepInHour
State%BkSurf(KBkSurf)%WinDirBkAbs( L , I , J ) = Hold
END DO
END DO
ELSE
DO I = 1, 24
DO J = 1, NumOfTimeStepInHour
State%BkSurf(KBkSurf)%WinDirBkAbs(L, I, J) = 0.0d0
END DO
END DO
ENDIF
END DO !layer loop
END DO !back surface loop
! ********************************************************************************
! Allocation and calculation of integrated values for front of window surface
! ********************************************************************************
! Sum of front absorptances for each incident direction (integration of absorptances)
IF(.not.ALLOCATED(State%IntegratedFtAbs)) ALLOCATE(State%IntegratedFtAbs(Geom%Inc%NBasis))
DO J = 1, Geom%Inc%NBasis
Sum1 = 0.0d0
DO L = 1, State%NLayers !layer loop
Sum1 = Sum1 + Construct(IConst)%BSDFInput%Layer(L)%FrtAbs(1, J)
END DO
State%IntegratedFtAbs(J) = Sum1
END DO
! Integrating front transmittance
IF(.not.ALLOCATED(State%IntegratedFtTrans)) ALLOCATE(State%IntegratedFtTrans(Geom%Inc%NBasis))
DO J = 1, Geom%Inc%NBasis ! Incident ray loop
Sum1 = 0.0d0
DO M = 1, Geom%Trn%NBasis ! Outgoing ray loop
Sum1 =Sum1 + Geom%Trn%Lamda(J) * Construct(IConst)%BSDFInput%SolFrtTrans(M, J)
END DO ! Outgoing ray loop
State%IntegratedFtTrans(J) = Sum1
END DO ! Incident ray loop
IF(.not.ALLOCATED(State%IntegratedFtRefl)) ALLOCATE(State%IntegratedFtRefl(Geom%Inc%NBasis))
! Integrating front reflectance
DO J = 1 , Geom%Inc%NBasis ! Incoming ray loop
State%IntegratedFtRefl(J) = 1 - State%IntegratedFtTrans(J) - State%IntegratedFtAbs(J)
END DO !Incoming ray loop
! ********************************************************************************
! Allocation and calculation of integrated values for back of window surface
! ********************************************************************************
! Sum of back absorptances for each incident direction (integration of absorptances)
IF(.not.ALLOCATED(State%IntegratedBkAbs)) ALLOCATE(State%IntegratedBkAbs(Geom%Trn%NBasis))
DO J = 1, Geom%Trn%NBasis
Sum1 = 0.0d0
DO L = 1, State%NLayers !layer loop
Sum1 = Sum1 + Construct(IConst)%BSDFInput%Layer(L)%BkAbs(1, J)
END DO
State%IntegratedBkAbs(J) = Sum1
END DO
! Integrating back reflectance
if(.not.ALLOCATED(State%IntegratedBkRefl)) ALLOCATE(State%IntegratedBkRefl(Geom%Trn%NBasis))
DO J = 1, Geom%Trn%NBasis ! Outgoing ray loop
Sum1 = 0.0d0
DO M = 1, Geom%Inc%NBasis ! Incident ray loop
Sum1 = Sum1 + Geom%Inc%Lamda(J) * Construct(IConst)%BSDFInput%SolBkRefl(M, J)
END DO !Incident ray loop
State%IntegratedBkRefl(J) = Sum1
END DO !Outgoing ray loop
if(.not.ALLOCATED(State%IntegratedBkTrans)) ALLOCATE(State%IntegratedBkTrans(Geom%Trn%NBasis))
! Integrating back transmittance
DO J = 1 , Geom%Trn%NBasis ! Outgoing ray loop
State%IntegratedBkTrans(J) = 1 - State%IntegratedBkRefl(J) - State%IntegratedBkAbs(J)
END DO !Outgoing ray loop
RETURN
END SUBROUTINE CalcWindowStaticProperties