Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | tmean | |||
integer, | intent(in), | dimension(maxgas) | :: | iprop | ||
real(kind=r64), | intent(in), | dimension(maxgas) | :: | frct | ||
real(kind=r64), | intent(in) | :: | pres | |||
integer, | intent(in) | :: | nmix | |||
real(kind=r64), | intent(in), | dimension(maxgas) | :: | xwght | ||
real(kind=r64), | intent(in), | dimension(maxgas, 3) | :: | xgcon | ||
real(kind=r64), | intent(in), | dimension(maxgas, 3) | :: | xgvis | ||
real(kind=r64), | intent(in), | dimension(maxgas, 3) | :: | xgcp | ||
real(kind=r64), | intent(out) | :: | con | |||
real(kind=r64), | intent(out) | :: | visc | |||
real(kind=r64), | intent(out) | :: | dens | |||
real(kind=r64), | intent(out) | :: | cp | |||
real(kind=r64), | intent(out) | :: | pr | |||
integer, | intent(in) | :: | standard | |||
integer, | intent(out) | :: | nperr | |||
character(len=*), | intent(inout) | :: | ErrorMessage |
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 GASSES90(tmean,iprop,frct,pres,nmix,xwght,xgcon,xgvis,xgcp,con,visc,dens,cp,pr,standard,nperr,ErrorMessage)
! Variables
integer, intent(in) :: standard, nmix
integer, dimension(maxgas), intent(in) :: iprop
real(r64), dimension(maxgas), intent(in) :: xwght
real(r64), dimension(maxgas, 3), intent(in) :: xgcon, xgcp, xgvis
real(r64), intent(in) :: tmean, pres
real(r64), dimension(maxgas), intent(in) :: frct
integer, intent(out) :: nperr
character(len=*), intent(inout) :: ErrorMessage
real(r64), intent(out) :: con, visc, dens, cp, pr
integer :: i, j;
real(r64), dimension(maxgas) :: fvis, fcon, fdens, fcp
real(r64), dimension(maxgas) :: kprime, kdblprm, mukpdwn, kpdown, kdpdown
real(r64) :: molmix, cpmixm, kpmix, kdpmix, kmix, mumix
real(r64) :: phimup, downer, psiup, psiterm, phikup, rhomix
!Simon: TODO: this is used for EN673 calculations and it is not assigned properly. Check this
real(r64), dimension(maxgas, 3) :: xgrho
real(r64), dimension(maxgas, 3) :: grho
!real(r64) gaslaw
!DATA gaslaw /8314.51/ ! Molar gas constant in Joules/(kmol*K)
! SUBROUTINE PARAMETER DEFINITIONS:
real(r64), parameter :: ENpressure = 1.0d5 ! Gap gas pressure (Pa)
real(r64), parameter :: gaslaw = 8314.51d0 ! Molar gas constant (J/kMol-K)
!!! Body of GASSES90
con=0.0d0
visc=0.0d0
dens=0.0d0
cp=0.0d0
!Simon: remove this when assigned properly
!EPTeam??? xgrho = 0.0d0 !Objexx:Uninit Line added to protect against use uninitialized: Assuming this is incomplete/unused functionality
grho = 0.0d0
fcon(1) = xgcon(iprop(1),1) + xgcon(iprop(1),2)*tmean + xgcon(iprop(1),3)*tmean**2
fvis(1) = xgvis(iprop(1),1) + xgvis(iprop(1),2)*tmean + xgvis(iprop(1),3)*tmean**2
fcp(1) = xgcp(iprop(1),1) + xgcp(iprop(1),2)*tmean + xgcp(iprop(1),3)*tmean**2
! Density using ideal gas law: rho=(presure*mol. weight)/(gas const*Tmean)
fdens(1) = pres * xwght(iprop(1)) / (UniversalGasConst * tmean)
! Mollecular weights in kg/kmol
if ((standard.eq.EN673).or.(standard.eq.EN673Design)) then
!fdens(1) = xgrho(iprop(1),1) + xgrho(iprop(1),2)*tmean + xgrho(iprop(1),3)*tmean**2 !Objexx:Uninit xgrho is uninitialized
fdens(i) = ENpressure*xwght(iprop(i))/(gaslaw*tmean)
end if
if (frct(1).eq.1.0d0) then ! Single gas properties
visc=fvis(1) ! viscosity in kg/(m*s)
con=fcon(1) ! conductivity in W/(m*K)
cp=fcp(1) ! SpecIFic heat in J/(kg*K)
dens=fdens(1) ! density in kg/m^3
else ! Mixture properties
molmix = frct(1)*xwght(iprop(1)) ! initialize equation 56
cpmixm = molmix*fcp(1) ! initialize equation 58
kprime(1) = 3.75d0 * UniversalGasConst / xwght(iprop(1)) * fvis(1) ! equation 67
kdblprm(1) = fcon(1)-kprime(1) ! equation 67
! initialize sumations for eqns 60-66:
mumix = 0.0d0
kpmix = 0.0d0
kdpmix = 0.0d0
mukpdwn(1) = 1.0d0
kpdown(1) = 1.0d0
kdpdown(1) = 1.0d0
do i = 2, nmix
if (frct(i).eq.0.0d0) then
nperr = 2011 ! error 2011: component fraction in a mixture is 0%
ErrorMessage = 'Component fraction in mixture is 0%'
return
end if
! calculate properties of mixture constituents:
fcon(i) = xgcon(iprop(i),1) + xgcon(iprop(i),2)*tmean + xgcon(iprop(i),3)*tmean**2.0d0
fvis(i) = xgvis(iprop(i),1) + xgvis(iprop(i),2)*tmean + xgvis(iprop(i),3)*tmean**2.0d0
fcp(i) = xgcp(iprop(i),1) + xgcp(iprop(i),2)*tmean + xgcp(iprop(i),3)*tmean**2.0d0
fdens(i) = pres * xwght(iprop(i)) / (UniversalGasConst * tmean)
if ((standard.eq.EN673).or.(standard.eq.EN673Design)) then
!fdens(i) = grho(iprop(i),1) + grho(iprop(i),2)*tmean + grho(iprop(i),3)*tmean**2.0d0
fdens(1) = ENpressure*xwght(iprop(1))/(gaslaw*tmean) ! Density using ideal gas law: rho=(presure*mol. weight)/(gas const*Tmean)
end if
molmix = molmix+frct(i)*xwght(iprop(i)) ! equation 56
cpmixm = cpmixm+frct(i)*fcp(i)*xwght(iprop(i)) ! equation 58-59
kprime(i) = 3.75d0 * UniversalGasConst / xwght(iprop(i)) * fvis(i) ! equation 67
kdblprm(i) = fcon(i)-kprime(i) ! equation 68
mukpdwn(i) = 1.0d0 ! initialize denominator of equation 60
kpdown(i) = 1.0d0 ! initialize denominator of equation 63
kdpdown(i) = 1.0d0 ! initialize denominator of equation 65
end do
select case (standard)
case (ISO15099)
do i = 1, nmix
do j = 1, nmix
! numerator of equation 61
phimup = (1.0d0 + (fvis(i)/fvis(j))**0.5d0*(xwght(iprop(j))/xwght(iprop(i)))**0.25d0)**2.0d0
! denominator of equation 61, 64 and 66
downer = 2.0d0 * sqrt(2.0d0) * (1.0d0+(xwght(iprop(i))/xwght(iprop(j))))**0.5d0
! calculate the denominator of equation 60
if (i.ne.j) mukpdwn(i) = mukpdwn(i) + phimup/downer*frct(j)/frct(i)
! numerator of equation 64, psiterm is the multiplied term in backets
psiup = (1.0d0 + (kprime(i)/kprime(j))**0.5d0*(xwght(iprop(i))/xwght(iprop(j)))**0.25d0)**2.0d0
psiterm = 1.0d0 + 2.41d0*(xwght(iprop(i))-xwght(iprop(j)))*(xwght(iprop(i))-0.142d0*xwght(iprop(j))) &
/ (xwght(iprop(i)) + xwght(iprop(j)))**2.0d0
! using the common denominator downer calculate the denominator for equation 63
if (i.ne.j) kpdown(i) = kpdown(i) + psiup*psiterm/downer*frct(j)/frct(i)
! calculate the numerator of equation 66
phikup = (1.0d0+(kprime(i)/kprime(j))**0.5d0 * (xwght(iprop(i))/xwght(iprop(j)))**0.25d0)**2.0d0
! using the common denominator downer calculat the denominator for equation 65
if (i.ne.j) kdpdown(i) = kdpdown(i) + phikup/downer*frct(j)/frct(i)
end do
mumix = mumix + fvis(i)/mukpdwn(i) ! equation 60
kpmix = kpmix + kprime(i)/kpdown(i) ! equation 63
kdpmix = kdpmix + kdblprm(i)/kdpdown(i) ! equation 65
end do
! calculate the density of the mixture assuming an ideal gas:
rhomix = pres * molmix / (UniversalGasConst * tmean) ! equation 57
kmix = kpmix + kdpmix ! equation 68-a
! final mixture properties:
visc=mumix
con=kmix
dens=rhomix
cp=cpmixm/molmix
case (EN673, EN673Design)
do i=1,nmix
con = con + fcon(i)*frct(i)
visc = visc + fvis(i)*frct(i)
dens = dens + fdens(i)*frct(i)
cp = cp + fcp(i)*frct(i)
end do
case DEFAULT
! should never come here - unsupported standard
end select
end if
pr = cp * visc / con ! calculate the Prandtl number
end subroutine GASSES90