Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | tmean | |||
integer, | intent(in) | :: | IGap | |||
real(kind=r64), | intent(out) | :: | dens | |||
real(kind=r64), | intent(out) | :: | visc |
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 WindowGasPropertiesAtTemp(tmean,IGap,dens,visc)
! SUBROUTINE INFORMATION:
! AUTHOR F. Winkelmann
! DATE WRITTEN December 2002
! MODIFIED na
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Finds the density and viscosity of the gas in a gap at a particular temperature.
! The gap may be filled with a single gas or a gas mixture.
! Based on Subroutine WindowGasConductance.
! METHODOLOGY EMPLOYED:
! See Subr. WindowGasConductance
! REFERENCES:
! See Subr. WindowGasConductance
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT(IN) :: tmean ! Temperature of gas in gap (K)
INTEGER, INTENT(IN) :: IGap ! Gap number
REAL(r64), INTENT(OUT) :: dens ! Gap gas density at tmean (kg/m3)
REAL(r64), INTENT(OUT) :: visc ! Gap gas dynamic viscosity at tmean (g/m-s)
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: pres = 1.0d5 ! Gap gas pressure (Pa)
REAL(r64), PARAMETER :: gaslaw = 8314.51d0 ! Molar gas constant (J/kMol-K)
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
INTEGER :: IMix,i,j ! Counters of gases in a mixture
INTEGER :: NMix ! Number of gases in a mixture
REAL(r64) :: molmix ! Molecular weight of mixture
REAL(r64) :: mukpdwn(10) ! Denominator term
REAL(r64) :: mumix ! For accumulating viscosity of gas mixture
REAL(r64) :: phimup ! Numerator factor
REAL(r64) :: downer ! Denominator factor
REAL(r64) :: rhomix ! Density of gas mixture (kg/m3)
REAL(r64) :: frct(10) ! Fraction of each gas in a mixture
REAL(r64) :: fvis(10) ! Viscosity of each gas in a mixture (g/m-s)
REAL(r64) :: fdens(10) ! Density of each gas in a mixture (kg/m3)
NMix = gnmix(IGap)
DO IMix = 1,NMix
frct(IMix) = gfract(IGap,IMix)
END DO
fvis(1) = gvis(IGap,1,1) + gvis(IGap,1,2)*tmean + gvis(IGap,1,3)*tmean**2
fdens(1) = pres*gwght(IGap,1)/(gaslaw*tmean) ! Density using ideal gas law:
! rho=(presure*molecweight)/(gasconst*tmean)
IF(NMix == 1) then ! Single gas
visc =fvis(1)
dens =fdens(1)
else ! Multiple gases; calculate mixture properties
molmix = frct(1)*gwght(IGap,1) ! initialize eq. 56
! Initialize summations for eqns 60-66
mumix = 0.0d0
mukpdwn(1) = 1.0d0
! Calculate properties of mixture constituents
do i = 2, NMix
fvis(i) = gvis(IGap,i,1) + gvis(IGap,i,2)*tmean + gvis(IGap,i,3)*tmean**2
fdens(i) = pres*gwght(IGap,i)/(gaslaw*tmean)
molmix = molmix+frct(i)*gwght(IGap,i) ! eq. 56
mukpdwn(i) = 1.0d0 ! initialize denomonator of eq. 60
end do
do i = 1,NMix
do j = 1,NMix
! numerator of equation 61
phimup = (1.0d0 + (fvis(i)/fvis(j))**0.5d0*(gwght(IGap,j)/gwght(IGap,i))**0.25d0)**2
! denomonator of eq. 61, 64 and 66
downer = 2.d0 * sqrt(2.d0) * (1+(gwght(IGap,i)/gwght(IGap,j)))**0.5d0
! calculate the denominator of eq. 60
if (i /= j) mukpdwn(i) = mukpdwn(i) + phimup/downer*frct(j)/frct(i)
end do
mumix = mumix + fvis(i)/mukpdwn(i) ! eq. 60
end do
! Calculate the density of the mixture assuming an ideal gas
rhomix = pres * molmix / (gaslaw * tmean) ! eq. 57
! Final mixture properties
visc=mumix
dens=rhomix
endif ! End of check if single or multiple gases in gap
RETURN
END SUBROUTINE WindowGasPropertiesAtTemp