Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | IHOUR | |||
integer, | intent(in) | :: | NBKS | |||
integer, | intent(in) | :: | HTSS | |||
integer, | intent(in) | :: | GRSNR | |||
integer, | intent(in) | :: | TS |
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 CalcInteriorSolarOverlaps(IHOUR,NBKS,HTSS,GRSNR,TS)
! SUBROUTINE INFORMATION:
! AUTHOR Fred Winkelmann
! DATE WRITTEN January 1999
! MODIFIED Nov 2001, FW: include beam radiation overlaps with
! back windows and doors; previously these subsurfaces ignored.
! May 2002, FW: fix problem where reveal was not being considered
! in calculating overlap areas if window is shaded only by reveal.
! June 2002, FW: fix problem that gave incorrect calculation when
! window is not shaded only by reveal
! June 2002, FW: remove incorrect multiplication of overlap areas
! by sunlit fraction when window is shaded only by reveal
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! For an exterior window with surface number HTSS, determines (1) the surface numbers of back
! surfaces receiving beam radiation from the window and (2) for each such back surface, the area
! of the portion of the window sending beam radiation to the back surface; this is called the
! "overlap area."
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! BLAST/IBLAST code, original author George Walton
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: IHOUR ! Hour Index
INTEGER, INTENT(IN) :: TS ! Time step Index
INTEGER, INTENT(IN) :: HTSS ! Surface number of the subsurface (exterior window)
INTEGER, INTENT(IN) :: GRSNR ! General receiving surface number (base surface of the exterior window)
INTEGER, INTENT(IN) :: NBKS ! Number of back surfaces associated with this GRSNR (in general, only
! some of these will receive beam radiation from HTSS this hour)
! SUBROUTINE PARAMETER DEFINITIONS:
INTEGER, PARAMETER :: None = 0 ! for use with RevealStatus
INTEGER, PARAMETER :: EntireWindowShadedByReveal = 1 ! for use with RevealStatus
INTEGER, PARAMETER :: WindowShadedOnlyByReveal = 2 ! for use with RevealStatus
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: I,J ! DO loop index
INTEGER :: IBKS ! Back surface DO loop index
INTEGER :: JBKS ! Counter of back surfaces with non-zero overlap with HTSS
INTEGER :: JBKSbase ! Back base surface counter
INTEGER :: BackSurfNum ! Back surface number
REAL(r64) :: OverlapArea ! Overlap area (m2)
LOGICAL :: UseSimpleDistribution ! TRUE means simple interior solar distribution
! (all incoming beam assumed to strike floor),
! FALSE means exact interior solar distribution
! (track which back surfaces beam illuminates)
IF (SAREA(HTSS) > 0.0d0) THEN
UseSimpleDistribution = .FALSE.
IF ((NBKS <= 0).OR.(Surface(GRSNR)%ExtBoundCond > 0)) THEN
UseSimpleDistribution = .TRUE.
ELSE
! Using 'exact' distribution, replace subsurface HC entries with reveal HC entries
! so that the reveal HC is used in calculating interior solar overlap areas
! Adding the following line fixes a problem where, if the window was shaded only
! by reveal, then the reveal was not considered in calculating interior solar
! overlap areas (FCW 5/3/02).
!IF(Surface(HTSS)%Reveal > 0.0) NRVLHC = 1
! Changing the line to the following avoids incorrect calculation when window is not shaded
! only by reveal (FCW 6/28/02).
IF(WindowRevealStatus(HTSS,IHOUR,TS) == WindowShadedOnlyByReveal) NRVLHC = 1
IF (NRVLHC > 0) THEN
DO I = 1, NRVLHC
HCT(FSBSHC-1+I) = HCT(FRVLHC-1+I)
HCNV(FSBSHC-1+I) = HCNV(FRVLHC-1+I)
HCAREA(FSBSHC-1+I) = HCAREA(FRVLHC-1+I)
DO J = 1, MAXHCV
HCX(J,FSBSHC-1+I) = HCX(J,FRVLHC-1+I)
HCY(J,FSBSHC-1+I) = HCY(J,FRVLHC-1+I)
HCA(J,FSBSHC-1+I) = HCA(J,FRVLHC-1+I)
HCB(J,FSBSHC-1+I) = HCB(J,FRVLHC-1+I)
HCC(J,FSBSHC-1+I) = HCC(J,FRVLHC-1+I)
END DO
END DO
NSBSHC=NRVLHC
END IF
END IF
! Check for array space.
IF (FSBSHC+NBKSHC > MAXHCS) UseSimpleDistribution = .TRUE.
IF (.NOT.UseSimpleDistribution) THEN ! Compute overlaps
FINSHC = FSBSHC + NSBSHC
JBKS = 0
JBKSbase = 0
DO IBKS = 1, NBKSHC ! Loop over back surfaces to GRSNR this hour. NBKSHC is the number of
! back surfaces that would receive beam radiation from the base surface, GRSNR,
! if the base surface was transparent. In general, some (at least one) or all of these
! will receive beam radiation from the exterior window subsurface, HTSS, of GRSNR,
! depending on the size of HTSS and its location on GRSNR
BackSurfNum = HCNS(FBKSHC-1+IBKS)
! Determine if this back surface number can receive beam radiation from the
! exterior window, HTSS, this hour, i.e., overlap area is positive
LOCHCA = FINSHC - 1
CALL MULTOL(FBKSHC-1+IBKS,FSBSHC-1,NSBSHC)
! Compute overlap area for this back surface
NINSHC = LOCHCA - FINSHC + 1
IF (NINSHC <= 0) CYCLE
OverlapArea = HCAREA(FINSHC)
DO J = 2, NINSHC
OverlapArea = OverlapArea + HCAREA(FINSHC-1+J)*(1.0d0-HCT(FINSHC-1+J))
END DO
IF(OverlapArea > 0.001d0) THEN
JBKS = JBKS + 1
IF(Surface(BackSurfNum)%BaseSurf == BackSurfNum) JBKSbase = JBKS
IF(JBKS <= MaxBkSurf) THEN
BackSurfaces(HTSS,JBKS,IHOUR,TS) = BackSurfNum
! Remove following IF check: multiplying by sunlit fraction in the following is incorrect
! (FCW, 6/28/02)
!IF (WindowRevealStatus(HTSS,IHOUR,TS) == WindowShadedOnlyByReveal) THEN
! OverlapArea = OverlapArea*(SAREA(HTSS)/Surface(HTSS)%Area)
!ENDIF
OverlapAreas(HTSS,JBKS,IHOUR,TS) = OverlapArea*SurfaceWindow(HTSS)%GlazedFrac
! If this is a subsurface, subtract its overlap area from the base surface
IF(Surface(BackSurfNum)%BaseSurf /= BackSurfNum .AND. JBKSbase /= 0) THEN
OverlapAreas(HTSS,JBKSbase,IHOUR,TS) = MAX(0.0d0, &
OverlapAreas(HTSS,JBKSbase,IHOUR,TS)- OverlapAreas(HTSS,JBKS,IHOUR,TS))
END IF
END IF
END IF
END DO ! End of loop over back surfaces
END IF
END IF ! End of check that sunlit area > 0.
RETURN
END SUBROUTINE CalcInteriorSolarOverlaps