Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | N | |||
real(kind=r64), | intent(in), | DIMENSION(N) | :: | A | ||
real(kind=r64), | intent(in), | DIMENSION(N) | :: | Azimuth | ||
real(kind=r64), | intent(in), | DIMENSION(N) | :: | Tilt | ||
real(kind=r64), | intent(out), | DIMENSION(N,N) | :: | F | ||
integer, | intent(in), | DIMENSION(N) | :: | SPtr |
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 CalcApproximateViewFactors(N,A,Azimuth,Tilt,F,SPtr)
! SUBROUTINE INFORMATION:
! AUTHOR Curt Pedersen
! DATE WRITTEN July 2000
! MODIFIED March 2001 (RKS) to disallow surfaces facing the same direction to interact radiatively
! May 2002 (COP) to include INTMASS, FLOOR, ROOF and CEILING.
! RE-ENGINEERED September 2000 (RKS for EnergyPlus)
! PURPOSE OF THIS SUBROUTINE:
! This subroutine approximates view factors using an area weighting.
! This is improved by one degree by not allowing surfaces facing the same
! direction to "see" each other.
! METHODOLOGY EMPLOYED:
! Each surface sees some area of other surfaces within the zone. The view
! factors from the surface to the other seen surfaces are defined by their
! area over the summed area of seen surfaces. Surfaces facing the same angle
! are assumed to not be able to see each other.
! Modified May 2002 to cover poorly defined surface orientation. Now all thermal masses, roofs and
! ceilings are "seen" by other surfaces. Floors are seen by all other surfaces, but
! not by other floors.
! REFERENCES:
! na
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENTS:
INTEGER, INTENT (IN) :: N ! NUMBER OF SURFACES
REAL(r64), INTENT (IN), DIMENSION(N) :: A ! AREA VECTOR- ASSUMED,BE N ELEMENTS LONG
REAL(r64), INTENT (IN), DIMENSION(N) :: Azimuth ! Facing angle of the surface (in degrees)
REAL(r64), INTENT (IN), DIMENSION(N) :: Tilt ! Tilt angle of the surface (in degrees)
REAL(r64), INTENT (OUT), DIMENSION(N,N) :: F ! APPROXIMATE DIRECT VIEW FACTOR MATRIX (N X N)
INTEGER, INTENT (IN), DIMENSION(N) :: SPtr ! pointer to REAL(r64) surface number (for error message)
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: SameAngleLimit = 10.0d0 ! If the difference in the azimuth angles are above this value (degrees),
! then the surfaces are assumed to be facing different directions.
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: I, J ! DO loop counters for surfaces in the zone
REAL(r64), ALLOCATABLE, DIMENSION(:) :: ZoneArea ! Sum of the area of all zone surfaces seen
! FLOW:
! Calculate the sum of the areas seen by all zone surfaces
ALLOCATE(ZoneArea(N))
ZoneArea = 0.0d0
DO I = 1, N
DO J = 1, N
! Assumption is that a surface cannot see itself or any other surface
! that is facing the same direction (has the same azimuth)
! Modified to use Class of surface to permit INTMASS to be seen by all surfaces,
! FLOOR to be seen by all except other floors, and ROOF and CEILING by all.
!
! Skip same surface
!
IF (I== J) cycle
!
! Include INTMASS, FLOOR(for others), CEILING, ROOF and different facing surfaces.
!
IF ( (Surface(SPtr(J))%Class == SurfaceClass_IntMass) .OR. & ! Everything sees internal mass surfaces
(Surface(SPtr(J))%Class == SurfaceClass_Floor) .OR. & ! Everything except other floors sees floors
(Surface(SPtr(J))%Class == SurfaceClass_Roof .AND. Surface(SPtr(I))%Class == SurfaceClass_Floor) .OR. &
! Roofs/ceilings always see floors
((ABS(Azimuth(I)-Azimuth(J)) > SameAngleLimit).OR. (ABS(Tilt(I)-Tilt(J)) > SameAngleLimit) ) ) THEN
ZoneArea(I) = ZoneArea(I) + A(J)
END IF
END DO
IF (ZoneArea(I) <= 0.0d0) THEN
CALL ShowWarningError('CalcApproximateViewFactors: Zero area for all other zone surfaces.')
CALL ShowContinueError('Happens for Surface="'//TRIM(Surface(SPtr(I))%Name)//'" in Zone='// &
TRIM(Zone(Surface(SPtr(I))%Zone)%Name))
ENDIF
END DO
! Set up the approximate view factors. First these are initialized to all zero.
! This will clear out any junk leftover from whenever. Then, for each zone
! surface, set the view factor from that surface to other surfaces as the
! area of the other surface divided by the sum of the area of all zone surfaces
! that the original surface can actually see (calculated above). This will
! allow that the sum of all view factors from the original surface to all other
! surfaces will equal unity. F(I,J)=0 if I=J or if the surfaces face the same
! direction.
!
! Modified to use Class of surface to permit INTMASS to be seen by all surfaces,
! FLOOR to be seen by all except other floors, and ROOF and CEILING by all.
!
! The second IF statement is intended to avoid a divide by zero if
! there are no other surfaces in the zone that can be seen.
F = 0.0d0
DO I = 1, N
DO J = 1, N
! Skip same surface
IF (I== J) cycle
!
! Include INTMASS, FLOOR(for others), CEILING/ROOF and different facing surfaces.
!
IF ( (Surface(SPtr(J))%Class == SurfaceClass_IntMass) .OR. &
(Surface(SPtr(J))%Class == SurfaceClass_Floor) .OR. &
(Surface(SPtr(J))%Class == SurfaceClass_Roof) .OR. &
((ABS(Azimuth(I)-Azimuth(J)) > SameAngleLimit).OR. &
(ABS(Tilt(I)-Tilt(J)) > SameAngleLimit) ) ) THEN
IF (ZoneArea(I) > 0.0d0) F(I,J) = A(J)/(ZoneArea(I))
END IF
END DO
END DO
DEALLOCATE(ZoneArea)
RETURN
END SUBROUTINE CalcApproximateViewFactors