Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | tilt | |||
real(kind=r64), | intent(in), | dimension(maxlay2) | :: | theta | ||
real(kind=r64), | intent(in), | dimension(maxlay1) | :: | Tgap | ||
integer, | intent(in) | :: | nlayer | |||
real(kind=r64), | intent(in) | :: | height | |||
real(kind=r64), | intent(in), | dimension(MaxGap) | :: | gap | ||
integer, | intent(in), | dimension(maxlay1, maxgas) | :: | iprop | ||
real(kind=r64), | intent(in), | dimension(maxlay1, maxgas) | :: | frct | ||
real(kind=r64), | intent(in) | :: | VacuumPressure | |||
real(kind=r64), | intent(in), | dimension(maxlay1) | :: | presure | ||
integer, | intent(in), | dimension(maxlay1) | :: | nmix | ||
real(kind=r64), | intent(in), | dimension(maxgas) | :: | wght | ||
real(kind=r64), | intent(in), | dimension(maxgas, 3) | :: | gcon | ||
real(kind=r64), | intent(in), | dimension(maxgas, 3) | :: | gvis | ||
real(kind=r64), | intent(in), | dimension(maxgas, 3) | :: | gcp | ||
real(kind=r64), | intent(in), | dimension(maxgas) | :: | gama | ||
real(kind=r64), | intent(out), | dimension(maxlay1) | :: | hcgas | ||
real(kind=r64), | intent(out), | dimension(maxlay) | :: | Rayleigh | ||
real(kind=r64), | intent(out), | dimension(maxlay) | :: | Nu | ||
integer, | intent(inout) | :: | 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.
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 filmg(tilt, theta, Tgap, nlayer, height, gap, iprop, frct, VacuumPressure, presure, &
nmix, wght, gcon, gvis, gcp, gama, hcgas, Rayleigh, Nu, nperr, ErrorMessage)
!***********************************************************************
! sobroutine to calculate effective conductance of gaps
!***********************************************************************
! Inputs:
! tilt window angle (deg)
! theta vector of surface temperatures [K]
! nlayer total number of glazing layers
! height glazing cavity height
! gap vector of gap widths [m]
! iprop
! frct
! presure
! nmix vector of number of gasses in a mixture for each gap
! Output:
! hgas vector of gap coefficients
! nperr error code
! Locals:
! gr gap grashof number
! con gap gas conductivity
! visc dynamic viscosity @ mean temperature [g/m*s]
! dens density @ mean temperature [kg/m^3]
! cp specific heat @ mean temperature [J/g*K]
! pr gap gas Prandtl number
! tmean average film temperature
! delt temperature difference
real(r64), intent(in) :: tilt, height, VacuumPressure
real(r64), dimension(maxlay2), intent(in) :: theta
real(r64), dimension(maxlay1), intent(in) :: Tgap
real(r64), dimension(MaxGap), intent(in) :: gap
real(r64), dimension(maxlay1), intent(in) :: presure
real(r64), dimension(maxlay1, maxgas), intent(in) :: frct
real(r64), dimension(maxgas), intent(in) :: wght, gama
real(r64), dimension(maxgas, 3), intent(in) :: gcon, gvis, gcp
integer, intent(in) :: nlayer
integer, dimension(maxlay1, maxgas), intent(in) :: iprop
integer, dimension(maxlay1), intent(in) :: nmix
real(r64), dimension(maxlay), intent(out) :: Rayleigh, Nu
real(r64), dimension(maxlay1), intent(out) :: hcgas
integer, intent (inout) :: nperr
character(len=*), intent (inout) :: ErrorMessage
real(r64) :: con, visc, dens, cp, pr, delt, tmean, ra, asp, gnu
real(r64), dimension(maxgas) :: frctg
integer :: ipropg(maxgas), i, j, k, l
hcgas = 0.0d0
do i=1, nlayer-1
j = 2*i
k = j+1
! determine the gas properties of each gap:
!tmean = (theta(j)+theta(k))/2.
tmean = Tgap(i+1) ! Tgap(1) is exterior environment
delt = ABS(theta(j)-theta(k))
! Temperatures should not be equal. This can happen in initial temperature guess before iterations started
if (delt == 0.0d0) delt = 1.0d-6
do l=1, nmix(i+1)
ipropg(l) = iprop(i+1,l)
frctg(l) = frct(i+1,l)
end do
if (presure(i+1).gt.VacuumPressure) then
call gasses90(tmean, ipropg, frctg, presure(i+1), nmix(i+1), wght, gcon, gvis, gcp, con, visc, dens, cp, pr, &
ISO15099, nperr, ErrorMessage)
! Calculate grashoff number:
! The grashoff number is the Rayleigh Number (equation 5.29) in SPC142 divided by the Prandtl Number (prand):
ra = GravityConstant * gap(i)**3 * delt* cp * dens**2 / (tmean*visc*con)
Rayleigh(i) = ra
! write(*,*) 'height,gap(i),asp',height,gap(i),asp
!asp = 1
!if (gap(i).ne.0) then
asp = height / gap(i)
!end if
! determine the Nusselt number:
call nusselt(tilt, ra, asp, gnu, nperr, ErrorMessage)
Nu(i) = gnu
! calculate effective conductance of the gap
hcgas(i+1) = con/gap(i)*gnu
! write(*,*)'theta(j),theta(k),j,k',j,theta(j),k,theta(k)
! write(*,*)'Nusselt,Rayleigh,Prandtl,hgas(k),k'
! write(*,*) gnu,gr*pr,pr,hgas(k),k
else !low pressure calculations
call GassesLow(tmean, wght(iprop(i+1, 1)), presure(i+1), gama(iprop(i+1, 1)), con, nperr, ErrorMessage)
hcgas(i+1) = con
end if !if (pressure(i+1).gt.VacuumPressure) then
end do
end subroutine filmg