Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | N | |||
real(kind=r64), | intent(in), | DIMENSION(N) | :: | A | ||
real(kind=r64), | intent(in), | DIMENSION(N,N) | :: | F | ||
real(kind=r64), | intent(inout), | DIMENSION(N) | :: | EMISS | ||
real(kind=r64), | intent(out), | DIMENSION(N,N) | :: | ScriptF |
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 CalcScriptF(N,A,F,EMISS,ScriptF)
! SUBROUTINE INFORMATION:
! AUTHOR Curt Pedersen
! DATE WRITTEN 1980
! MODIFIED July 2000 (COP for the ASHRAE Loads Toolkit)
! RE-ENGINEERED September 2000 (RKS for EnergyPlus)
! PURPOSE OF THIS SUBROUTINE:
! Determines Hottel's ScriptF coefficients which account for the total
! grey interchange between surfaces in an enclosure.
! METHODOLOGY EMPLOYED:
! See reference
! REFERENCES:
! Hottel, H. C. and A. F. Sarofim, Radiative Transfer, Ch 3, McGraw Hill, 1967.
! 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,N) :: F ! DIRECT VIEW FACTOR MATRIX (N X N)
! --Must satisfy reciprocity and completeness:
! A(i)*F(i,j)=A(j)*F(j,i); F(i,i)=0.; SUM(F(i,j)=1.0, j=1,N)
REAL(r64), INTENT (INOUT), DIMENSION(N) :: EMISS ! VECTOR OF SURFACE EMISSIVITIES
REAL(r64), INTENT (OUT), DIMENSION(N,N) :: ScriptF ! MATRIX OF SCRIPT F FACTORS (N X N)
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: MaxEmissLimit = 0.99999d0 ! Limit the emissivity internally/avoid a divide by zero error
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: I, J ! DO loop counters (for rows and columns of matrices)
INTEGER :: K
REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: AF ! = (AREA * DIRECT VIEW FACTOR) MATRIX
REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: Cinverse ! Inverse of Cmatrix
REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: Cmatrix ! = (AF- EMISS/REFLECTANCE) MATRIX
REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: ExciteMatrix ! EXCITATION VECTOR = A*EMISS/REFLECTANCE
REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: Jmatrix ! MATRIX OF PARTIAL RADIOSITIES
! FLOW:
! Allocate and zero arrays
#ifdef EP_Count_Calls
NumCalcScriptF_Calls=NumCalcScriptF_Calls+1
#endif
ALLOCATE(AF(N,N))
ALLOCATE(Cinverse(N,N))
ALLOCATE(Cmatrix(N,N))
ALLOCATE(ExciteMatrix(N,N))
AF = 0.0d0
Cmatrix = 0.0d0
Cinverse = 0.0d0
ExciteMatrix = 0.0d0
ScriptF = 0.0d0
! Set up AF matrix.
DO I=1,N
DO J = 1,N
AF(I,J)=F(I,J)*A(I)
END DO
END DO
Cmatrix = AF ! Cmatrix is now same as AF
! Limit EMISS for any individual surface. This is to avoid
! an obvious divide by zero error in the next section
DO I=1,N
IF (EMISS(I) > MaxEmissLimit) THEN
EMISS(I) = MaxEmissLimit
CALL ShowWarningError('A thermal emissivity above 0.99999 was detected. This is not allowed. Value was reset to 0.99999')
END IF
END DO
DO I=1,N
ExciteMatrix(I,I) = -A(I)*EMISS(I)/(1.d0-EMISS(I)) ! Set up matrix columns for partial radiosity calculation
Cmatrix(I,I) = AF(I,I) - A(I)/(1.d0-EMISS(I)) ! Coefficient matrix for partial radiosity calculation
END DO
DEALLOCATE(AF)
CALL CalcMatrixInverse(Cmatrix,Cinverse) ! SOLVE THE LINEAR SYSTEM
DEALLOCATE(Cmatrix)
ALLOCATE(Jmatrix(N,N))
! Jmatrix = 0.0
Jmatrix = MATMUL(Cinverse,Excitematrix) ! Jmatrix columns contain partial radiosities
! DO i=1,N
! DO j=1,N
! DO k=1,N
! Jmatrix(i,j) = Jmatrix(i,j) + Cinverse(i,k) * Excitematrix(k,j)
! END DO
! END DO
! END DO
! Form Script F matrix
DO I=1,N
DO J=1,N
IF (I == J) THEN
! ScriptF(I,J) = EMISS(I)/(1.0d0-EMISS(I))*(Jmatrix(I,J)-Delta*EMISS(I)), where Delta=1
ScriptF(I,J) = EMISS(I)/(1.d0-EMISS(I))*(Jmatrix(I,J)-EMISS(I))
ELSE
! ScriptF(I,J) = EMISS(I)/(1.0d0-EMISS(I))*(Jmatrix(I,J)-Delta*EMISS(I)), where Delta=0
ScriptF(I,J) = EMISS(I)/(1.d0-EMISS(I))*(Jmatrix(I,J))
END IF
END DO
END DO
DEALLOCATE(Cinverse)
DEALLOCATE(ExciteMatrix)
DEALLOCATE(Jmatrix)
RETURN
END SUBROUTINE CalcScriptF