Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | NGRS | |||
integer, | intent(in) | :: | CurSurf | |||
integer, | intent(in) | :: | NBKS | |||
integer, | intent(in) | :: | HTS |
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 SHDBKS(NGRS,CurSurf,NBKS,HTS)
! SUBROUTINE INFORMATION:
! AUTHOR Legacy Code
! DATE WRITTEN
! MODIFIED na
! RE-ENGINEERED Lawrie, Oct 2000
! PURPOSE OF THIS SUBROUTINE:
! This is the driving subroutine for computing
! the sunlit areas for back surfaces.
! 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) :: NGRS ! Number of the general receiving surface
INTEGER, INTENT(IN) :: CurSurf
INTEGER, INTENT(IN) :: HTS ! Heat transfer surface number of the general receiving surf
INTEGER, INTENT(IN) :: NBKS ! Number of back surfaces
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER I
INTEGER M
INTEGER N
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
LOGICAL, SAVE :: OneTimeFlag=.true.
INTEGER BackSurfaceNumber
INTEGER NS1 ! Number of the figure being overlapped
INTEGER NS2 ! Number of the figure doing overlapping
INTEGER NS3 ! Location to place results of overlap
IF (OneTimeFlag) THEN
ALLOCATE(XVT(MaxVerticesPerSurface+1))
ALLOCATE(YVT(MaxVerticesPerSurface+1))
ALLOCATE(ZVT(MaxVerticesPerSurface+1))
XVT=0.0d0
YVT=0.0d0
ZVT=0.0d0
OneTimeFlag=.false.
ENDIF
IF ( (NBKS <= 0).OR.(SAREA(HTS) <= 0.0d0).OR. &
(OverlapStatus == TooManyVertices).OR. &
(OverlapStatus == TooManyFigures) ) RETURN
FBKSHC = LOCHCA + 1
DO I = 1, NBKS ! Loop through all back surfaces associated with the receiving surface
BackSurfaceNumber = ShadowComb(CurSurf)%BackSurf(I)
IF (CTHETA(BackSurfaceNumber) > -SunIsUpValue) CYCLE !-0.001) CYCLE ! go to next back surface since inside of this surface
! cannot be in sun if the outside can be
! Transform coordinates of back surface from general system to the
! plane of the receiving surface
CALL CTRANS(BackSurfaceNumber,NGRS,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
HCT(NS3) = 0.0d0
CALL HTRANS1(NS3,NVT)
! Adjust near-duplicate points.
NVR = HCNV(1)
DO N = 1, NVT
DO M = 1, NVR
IF (ABS(HCX(M,1)-HCX(N,NS3)) > 6) CYCLE
IF (ABS(HCY(M,1)-HCY(N,NS3)) > 6) CYCLE
HCX(N,NS3) = HCX(M,1)
HCY(N,NS3) = HCY(M,1)
END DO
END DO
CALL HTRANS0(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
! Increment back surface count.
LOCHCA = NS3
HCNS(LOCHCA) = BackSurfaceNumber
HCAREA(LOCHCA) = -HCAREA(LOCHCA)
NBKSHC = LOCHCA - FBKSHC + 1
END DO
RETURN
END SUBROUTINE SHDBKS