Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | delt | |||
integer, | intent(in) | :: | SolutionDimensions |
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 CalculateGammas(delt,SolutionDimensions)
! SUBROUTINE INFORMATION:
! AUTHOR Russ Taylor
! DATE WRITTEN June 1990
! MODIFIED na
! RE-ENGINEERED July 1996, RKS
! PURPOSE OF THIS SUBROUTINE:
! Compute gammas as defined in Seem's dissertation.
! Runs as a subroutine of the conduction transfer
! function solver (InitializeCTFs).
! METHODOLOGY EMPLOYED:
! Determine the Gamma1 and Gamma2 based on the results
! from the ExponMatrix and InvertMatrix subroutines.
! This routine is specialized to take advantage of the
! fact that most of BMat consists of zeroes.
! REFERENCES:
! The state space method of calculating CTFs is
! outlined in the doctoral dissertation of John Seem,
! "Modeling of Heat Transfer in Buildings", Department
! of Mechanical Engineering, University of Wisconsin-
! Madison, 1987.
! USE STATEMENTS:
! none
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT(IN) :: delt ! Time increment in fraction of an hour
INTEGER, INTENT(IN) :: SolutionDimensions ! Integer relating whether a 1- or 2-D solution is required
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64), ALLOCATABLE, DIMENSION(:,:) :: ATemp ! Intermediate variable equal to AExp - I
INTEGER :: i ! Loop counter
INTEGER :: is1 ! Loop counter
INTEGER :: j ! Loop counter
INTEGER :: SurfNode ! Loop counter
! FLOW:
! Compute Gamma1 from equation (2.1.12) in Seem's dissertation which
! states that: Gamma1 = [AInv] * ([AExp]-[I]) * [BMat]
! noting that BMat contains only the non-zero values of the B Matrix.
ALLOCATE(ATemp(rcmax,rcmax))
ATemp = AExp - IdenMatrix
Gamma1 = 0.0d0
DO i = 1,rcmax
DO is1 = 1,rcmax
IF (SolutionDimensions == 1) THEN
Gamma1(i,1) = Gamma1(i,1)+AInv(i,is1)*ATemp(is1,1)*BMat(1)
Gamma1(i,2) = Gamma1(i,2)+AInv(i,is1)*ATemp(is1,rcmax)*BMat(2)
ELSE ! SolutionDimensions = 2
DO SurfNode = 1, NumOfPerpendNodes
Gamma1(i,1) = Gamma1(i,1)+AInv(i,is1)*ATemp(is1,SurfNode)*BMat(1)
Gamma1(i,2) = Gamma1(i,2)+AInv(i,is1)*ATemp(is1,rcmax+1-SurfNode)*BMat(2)
END DO
END IF
IF (NodeSource > 0) THEN
Gamma1(i,3) = Gamma1(i,3)+AInv(i,is1)*ATemp(is1,NodeSource)*BMat(3)
END IF
END DO
END DO
DEALLOCATE(ATemp)
! Compute Gamma2 from equation (2.1.13) in Seem's dissertation which
! states that: Gamma2 = [AInv] * ([Gamma1]/delt - [BMat])
! again noting that BMat contains only the non-zero values of B.
Gamma2 = 0.0d0
DO i = 1,rcmax
DO j = 1,3
DO is1 = 1,rcmax
IF (SolutionDimensions == 1) THEN
IF ( (j == 1) .AND. (is1 == 1) ) THEN
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt-BMat(1))
ELSE IF ( (j == 2) .AND. (is1 == rcmax) ) THEN
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt-BMat(2))
ELSE IF ( (j == 3) .AND. (is1 == NodeSource) ) THEN
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt-BMat(3))
ELSE ! the element of the actual BMat is zero
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt)
END IF
ELSE ! SolutionDimensions = 2
IF ( (j == 1) .AND. ((is1 >= 1).AND.(is1 <= NumOfPerpendNodes)) ) THEN
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt-BMat(1))
ELSE IF ( (j == 2) .AND. ((is1 <= rcmax).AND.(is1 >= rcmax+1-NumOfPerpendNodes)) ) THEN
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt-BMat(2))
ELSE IF ( (j == 3) .AND. (is1 == NodeSource) ) THEN
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt-BMat(3))
ELSE ! the element of the actual BMat is zero
Gamma2(i,j) = Gamma2(i,j)+AInv(i,is1)*(Gamma1(is1,j)/delt)
END IF
END IF
END DO
END DO
END DO
RETURN ! The calculation of Gamma1 and Gamma2 is now complete.
END SUBROUTINE CalculateGammas