Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | breal | |||
real(kind=r64), | intent(in) | :: | Ts | |||
real(kind=r64), | intent(in) | :: | Tg | |||
real(kind=r64), | intent(out) | :: | hsg | |||
integer, | intent(in) | :: | scheme |
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 SLtoGL(breal,Ts,Tg,hsg, scheme)
!
! SUBROUTINE INFORMATION:
! AUTHOR John L. Wright, University of Waterloo,
! Mechanical Engineering, Advanced Glazing System Laboratory
! DATE WRITTEN Unknown
! MODIFIED na
!
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Returns the heat transfer coefficient, shade-to-glass
!
! METHODOLOGY EMPLOYED:
! na
!
! REFERENCES:
! na
! USE STATEMENTS:
! na
!
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT(IN):: breal ! distance from shade to glass (m)
REAL(r64), INTENT(IN):: Ts ! shade temperature (K)
REAL(r64), INTENT(IN):: Tg ! glass temperature (K)
INTEGER, INTENT(IN):: scheme !
REAL(r64), INTENT(OUT):: hsg ! the heat transfer coefficient, shade-to-glass, {W/m2K}
!
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: b
REAL(r64) :: Tavg
REAL(r64) :: P
REAL(r64) :: rho
REAL(r64) :: beta
REAL(r64) :: dvisc
REAL(r64) :: Cp
REAL(r64) :: k
REAL(r64) :: Rabsg
REAL(r64) :: Nubsg
! Flow
hsg = 0.0d0 ! default - large spacing, b
IF (scheme .eq. 1) then ! simple conduction layer, Nu=1
b=breal
If (b .LT. 0.00001d0) b=0.00001d0 ! avoid division by zero in
! calculation of this scheme
Tavg=(Ts+Tg)/2.d0 ! T for properties calculations
k= 0.02538d0+((Tavg - 290.d0)/10.d0)*(0.02614d0 - 0.02538d0) ! conductivity (W/m.K)
hsg=k/b
ELSE IF (scheme .eq. 2) then ! similar to Nu=1 but small penalty at
! larger Ra (Collins)
b=breal
if (b .LT. 0.00001d0) b=0.00001d0 ! avoid division by zero in
! calculation of this scheme
Tavg=(Ts+Tg)/2.d0 ! T for properties calculations
! properties of AIR
rho=PAtmSeaLevel/(287.097d0 * Tavg) ! density (kg/m3) <- temperature in (K)
beta=1.d0/Tavg ! thermal expansion coef(/K)
dvisc = (18.05d0 + ((Tavg - 290.d0)/10.d0) * (18.53d0 - 18.05d0)) * 1.0d-6
! dynamic viscosity (kg/m.sec) or (N.sec/m2)
Cp= 1044.66d0 - 0.31597d0*Tavg+0.000707908d0*Tavg**2 - 0.00000027034d0*Tavg**3
! specific heat at constant pressure (J/kg.K)
k= 0.02538d0+((Tavg - 290.d0)/10.d0)*(0.02614d0 - 0.02538d0) ! conductivity (W/m.K)
Rabsg= (9.81d0*beta*(b**3)*ABS(Ts-Tg)*(rho**2)*Cp)/(dvisc*k)
Nubsg=1.d0 + 0.2d0 * (1.0d0 -EXP(-0.005d0*Rabsg))
hsg=Nubsg*k/b
END IF ! end of scheme .eq. 2
RETURN
END SUBROUTINE SLtoGL