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 | ||
---|---|---|---|---|---|---|
type(BSDFGeomDescr), | intent(inout) | :: | Geom | |||
type(BSDFWindowGeomDescr), | intent(in) | :: | Window | |||
integer, | intent(in) | :: | ISurf |
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 CalcComplexWindowOverlap(Geom, Window, ISurf)
! SUBROUTINE INFORMATION:
! AUTHOR Simon Vidanovic
! DATE WRITTEN May 2012
! MODIFIED Simon Vidanovic (May 2013) - added overlaps calculations for daylighting
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! For each of basis directions on back surface of the window calculates
! overlap areas. It also calculates overlap areas and reflectances for daylighting calculations
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! na
! USE STATEMENTS:
USE vectors
USE DataHeatBalance, ONLY : Material
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, INTENT(IN) :: ISurf !Surface number of the complex fenestration
TYPE (BSDFWindowGeomDescr),INTENT(IN) :: Window !Window Geometry
TYPE (BSDFGeomDescr), INTENT(INOUT) :: Geom !State Geometry
! INTERFACE BLOCK SPECIFICATIONS
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: XShadowProjection ! temporary buffer
REAL(r64) :: YShadowProjection ! temporary buffer
REAL(r64) :: XSp !for calc BSDF projection direction
REAL(r64) :: YSp !for calc BSDF projection direction
REAL(r64) :: ZSp !for calc BSDF projection direction
REAL(r64) :: SdotX !temporary variable for manipulating .dot. product
REAL(r64) :: SdotY !temporary variable for manipulating .dot. product
REAL(r64) :: SdotZ !temporary variable for manipulating .dot. product
INTEGER :: BackSurfaceNumber ! current back surface number
INTEGER NVR
INTEGER NVT ! Number of vertices of back surface
REAL(r64), ALLOCATABLE, DIMENSION(:), SAVE :: XVT ! X,Y,Z coordinates of vertices of
REAL(r64), ALLOCATABLE, DIMENSION(:), SAVE :: YVT ! back surfaces projected into system
REAL(r64), ALLOCATABLE, DIMENSION(:), SAVE :: ZVT ! relative to receiving surface
INTEGER NS1 ! Number of the figure being overlapped
INTEGER NS2 ! Number of the figure doing overlapping
INTEGER NS3 ! Location to place results of overlap
INTEGER IRay ! Current ray of BSDF direction
INTEGER KBkSurf ! Current back surface
INTEGER BaseSurf ! Base surface number
INTEGER N, M
INTEGER CurBaseSurf ! Currnet base surface number for shadow overlap calcualtions
INTEGER curBackSurface ! Current back surface number for base surface
INTEGER LOCStore ! Use to store pointer to highes data in local array
! When that counter is used in this routine, it just
! can be taken back to old number because all results
! are stored within this routine
! Daylighting
INTEGER IConst ! Construction number of back surface
INTEGER InsideConLay ! Construction's inside material layer number
REAL(r64) :: VisibleReflectance ! Visible reflectance for inside surface material
REAL(r64) :: TotAOverlap ! Total overlap area for given outgoing direction
REAL(r64) :: TotARhoVisOverlap ! Total overlap area time reflectance for given outgoing direction
ALLOCATE(XVT(MaxVerticesPerSurface+1))
ALLOCATE(YVT(MaxVerticesPerSurface+1))
ALLOCATE(ZVT(MaxVerticesPerSurface+1))
XVT=0.0d0
YVT=0.0d0
ZVT=0.0d0
ALLOCATE(Geom%Aoverlap(Geom%Trn%NBasis, Window%NBkSurf))
Geom%Aoverlap = 0.0d0
ALLOCATE(Geom%ARhoVisOverlap(Geom%Trn%NBasis, Window%NBkSurf))
Geom%ARhoVisOverlap = 0.0d0
ALLOCATE(Geom%AveRhoVisOverlap(Geom%Trn%NBasis))
Geom%AveRhoVisOverlap = 0.0d0
! First to calculate and store coordinates of the window surface
LOCHCA = 1
BaseSurf = Surface(ISurf)%BaseSurf
! Base surface contains current window surface (ISurf).
! Since that is case, bellow transformation should always return ZVT = 0.0d0
! for every possible transformation
CALL CTRANS(ISurf,BaseSurf,NVT,XVT,YVT,ZVT)
! HTRANS routine is using coordinates stored in XVS and YVS in order to calculate
! surface area. Since both projections are equal to zero, then simply
! compy these values into XVS and YVS arrays
DO N = 1, NVT
XVS(N) = XVT(N)
YVS(N) = YVT(N)
END DO
! This calculates the area stored in XVS and YVS
!CALL HTRANS(1,LOCHCA,NVT)
CALL HTRANS1(LOCHCA,NVT)
!HCAREA(LOCHCA) = -HCAREA(LOCHCA)
! Calculation of overlap areas for each outgoing basis direction
DO IRay = 1, Geom%Trn%NBasis ! basis directions loop (on back surface)
! For current basis direction calculate dot product between window surface
! and basis direction. This will be used to calculate projection of each
! of the back surfaces to window surface for given basis direciton
SdotX = Surface(ISurf)%lcsx.dot.Geom%sTrn(IRay)
SdotY = Surface(ISurf)%lcsy.dot.Geom%sTrn(IRay)
SdotZ = Surface(ISurf)%lcsz.dot.Geom%sTrn(IRay)
XSp = -SdotX
YSp = -SdotY
ZSp = -SdotZ
! Projection of shadows for current basis direciton
IF (ABS(ZSp) > 1.d-4) THEN
XShadowProjection = XSp/ZSp
YShadowProjection = YSp/ZSp
IF (ABS(XShadowProjection) < 1.d-8) XShadowProjection=0.0d0
IF (ABS(YShadowProjection) < 1.d-8) YShadowProjection=0.0d0
ELSE
XShadowProjection = 0.0d0
YShadowProjection = 0.0d0
ENDIF
DO KBkSurf = 1 , Window%NBkSurf !back surf loop
!BaseSurf = Surface(ISurf)%BaseSurf
BackSurfaceNumber = ShadowComb(BaseSurf)%BackSurf(KBkSurf)
! Transform coordinates of back surface from general system to the
! plane of the receiving surface
CALL CTRANS(BackSurfaceNumber,BaseSurf,NVT,XVT,YVT,ZVT)
! Project "shadow" from back surface along sun's rays to receiving surface. Back surface vertices
! become clockwise sequential.
DO N = 1, NVT
XVS(N) = XVT(N) - XShadowProjection*ZVT(N)
YVS(N) = YVT(N) - YShadowProjection*ZVT(N)
END DO
! Transform to the homogeneous coordinate system.
NS3 = LOCHCA+1
!NS3 = LOCHCA
HCT(NS3) = 0.0d0
!CALL HTRANS(1,NS3,NVT)
CALL HTRANS1(NS3,NVT)
! Determine area of overlap of projected back surface and receiving surface.
NS1 = 1
NS2 = NS3
HCT(NS3) = 1.0d0
CALL DeterminePolygonOverlap(NS1,NS2,NS3)
IF (OverlapStatus == NoOverlap) CYCLE ! to next back surface
IF ( (OverlapStatus == TooManyVertices).OR. &
(OverlapStatus == TooManyFigures) ) EXIT ! back surfaces DO loop
LOCHCA = NS3
HCNS(LOCHCA) = BackSurfaceNumber
HCAREA(LOCHCA) = -HCAREA(LOCHCA)
Geom%Aoverlap(IRay, KBkSurf) = HCAREA(LOCHCA)
END DO ! DO KBkSurf = 1 , NBkSurf
! If some of back surfaces is contained in base surface, then need to substract shadow of subsurface
! from shadow on base surface. Reson is that above shadowing algorithm is calculating shadow wihtout
! influence of subsurfaces
DO KBkSurf = 1 , Window%NBkSurf !back surf loop
BackSurfaceNumber = ShadowComb(BaseSurf)%BackSurf(KBkSurf)
CurBaseSurf = Surface(BackSurfaceNumber)%BaseSurf
IF (CurBaseSurf /= BackSurfaceNumber) THEN
! Search if that base surface in list of back surfaces for current window
CurBackSurface = 0
DO N = 1, Window%NBkSurf
IF (ShadowComb(BaseSurf)%BackSurf(N) == CurBaseSurf) THEN
curBackSurface = N
EXIT
END IF
END DO
IF (CurBackSurface /= 0) THEN
Geom%Aoverlap(IRay, curBackSurface) = Geom%Aoverlap(IRay, curBackSurface) - Geom%Aoverlap(IRay, KBkSurf)
END IF
END IF
END DO
! Calculate overlap area times reflectance. This is necessary for complex fenestration daylighting calculations
TotAOverlap = 0.0d0
TotARhoVisOverlap = 0.0d0
DO KBkSurf = 1 , Window%NBkSurf !back surf loop
BackSurfaceNumber = ShadowComb(BaseSurf)%BackSurf(KBkSurf)
CurBaseSurf = Surface(BackSurfaceNumber)%BaseSurf
IConst = Surface(BackSurfaceNumber)%Construction
InsideConLay = Construct(IConst)%TotLayers
IF (SurfaceWindow(BackSurfaceNumber)%WindowModelType == WindowBSDFModel) THEN
VisibleReflectance = Construct(IConst)%ReflectVisDiffBack
ELSE
VisibleReflectance = (1.0d0 - Material(InsideConLay)%AbsorpVisible)
END IF
Geom%ARhoVisoverlap(IRay, KBkSurf) = Geom%Aoverlap(IRay, KBkSurf) * VisibleReflectance
TotAOverlap = TotAOverlap + Geom%Aoverlap(IRay, KBkSurf)
TotARhoVisOverlap = TotARhoVisOverlap + Geom%ARhoVisoverlap(IRay, KBkSurf)
END DO
IF (TotAOverlap /= 0.0d0) THEN
Geom%AveRhoVisOverlap(IRay) = TotARhoVisOverlap / TotAOverlap
END IF
END DO ! DO IRay = 1, Geom%Trn%NBasis
! Reset back shadowing counter since complex windows do not need it anymore
LOCHCA = 1
DEALLOCATE(XVT)
DEALLOCATE(YVT)
DEALLOCATE(ZVT)
end subroutine CalcComplexWindowOverlap