Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | Tg | |||
real(kind=r64), | intent(in) | :: | Td | |||
real(kind=r64), | intent(in) | :: | Tm | |||
real(kind=r64), | intent(in) | :: | rhog | |||
real(kind=r64), | intent(in) | :: | rhodf | |||
real(kind=r64), | intent(in) | :: | rhodb | |||
real(kind=r64), | intent(in) | :: | taud | |||
real(kind=r64), | intent(in) | :: | rhom | |||
real(kind=r64), | intent(out) | :: | hr_gm | |||
real(kind=r64), | intent(out) | :: | hr_gd | |||
real(kind=r64), | intent(out) | :: | hr_md |
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 DL_RES_r2 (Tg,Td,Tm,rhog,rhodf,rhodb,taud,rhom,hr_gm,hr_gd,hr_md)
!
! 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 radiant heat transfer coefficients between parallel surfaces:
!
! METHODOLOGY EMPLOYED:
! Solves radiant heat transfer coefficients between three parallel surfaces.
! The left and right surfcaes are opaque with reflectance rhog and rhom, respectively.
! And the middle layer is diathermanous with transmittance taud AND reflectance rhodf
! and rhodb on the left and rightsides, respectively.
! The subscripts g, d and m apply to Glass, Diathermanous layer, and mean-radiant room
! temperature in a configuration of a window with an indoor-side shading attachment
! but the analysis can be applied to any three layers in the configuration described
! above.
!
! REFERENCES:
! na
! USE STATEMENTS:
! na
!
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT(IN) :: Tg ! mean glass layer temperature, {K}
REAL(r64), INTENT(IN) :: Td ! mean diathermanous layer temperature, {K}
REAL(r64), INTENT(IN) :: Tm ! mean radiant room temperature, {K}
REAL(r64), INTENT(IN) :: rhog ! reflectance of glass layer, {-}
REAL(r64), INTENT(IN) :: rhodf ! front reflectance of diathermanous layer, {-}
REAL(r64), INTENT(IN) :: rhodb ! back reflectance of diathermanous layer, {-}
REAL(r64), INTENT(IN) :: taud ! transmittance of diathermanous layer, {-}
REAL(r64), INTENT(IN) :: rhom ! reflectance of the room, {-}
REAL(r64), INTENT(OUT):: hr_gm ! heat transfer coefficient between left and right surface {W/m2K}
REAL(r64), INTENT(OUT):: hr_gd ! heat transfer coefficient between left and middle surface {W/m2K}
REAL(r64), INTENT(OUT):: hr_md ! heat transfer coefficient between right and middle surface {W/m2K}
!
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: Epsg, Epsdf, Epsdb, Epsm
REAL(r64) :: A(20,22)
REAL(r64) :: X(20)
! real FSg_g, FSdf_g, FSdb_g, FSm_g
REAL(r64) :: FSg_df,FSdf_df,FSdb_df,FSm_df
REAL(r64) :: FSg_db,FSdf_db,FSdb_db,FSm_db
REAL(r64) :: FSg_m, FSdf_m, FSdb_m, FSm_m
! Calculate 4 emissivities/absorptivities
Epsg = 1.d0 - rhog
Epsdf = 1.d0 - rhodf - taud
Epsdb = 1.d0 - rhodb - taud
Epsm = 1.d0 - rhom
! Calculate script F shape factors
! FSx_y is the portion of radiation emitted
! by surface x that arrives at surface y
! via any path - including reflections
! By reciprocity FSxy=FSyx
! step 1: unit emission from (g) only
call SETUP4x4_A(rhog,rhodf,rhodb,taud,rhom,A)
A(1,5) = 1.0d0 ! unit source of radiation
call SOLMATS(4,A,X)
FSg_df = X(1)
! FSg_g = X(2)
FSg_m = X(3)
FSg_db = X(4)
! step 2: unit emission from (df) only
! call SETUP4x4_A(rhog,rhodf,rhodb,taud,rhom,A)
! A(2,5) = 1.0 ! unit source of radiation
! call SOLMATS(4,A,X)
! FSdf_df = X(1)
! FSdf_g = X(2)
! FSdf_m = X(3)
! FSdf_db = X(4)
! step 3: unit emission from (db) only
! call SETUP4x4_A(rhog,rhodf,rhodb,taud,rhom,A)
! A(3,5) = 1.0 ! unit source of radiation
! call SOLMATS(4,A,X)
! FSdb_df = X(1)
! FSdb_g = X(2)
! FSdb_m = X(3)
! FSdb_db = X(4)
! step 4: unit emission from (m) only
call SETUP4x4_A(rhog,rhodf,rhodb,taud,rhom,A)
A(4,5) = 1.0d0 ! unit source of radiation
call SOLMATS(4,A,X)
FSm_df = X(1)
! FSm_g = X(2)
! FSm_m = X(3)
FSm_db = X(4)
! calculate heat transfer coefficients
! hr_xy is the heat transfer coefficient from x to y [W/m2]
! Note: If the emissivity of either surface x or surface y is zero
! then q_xy will also be zero
! Note: This code has no problem with temperatures being equal
hr_gm = Epsg * Epsm * FSg_m * StefanBoltzmann * (Tg + Tm)*(Tg**2 + Tm**2)
hr_gd = Epsg * Epsdf * FSg_df * StefanBoltzmann * (Td + Tg)*(Td**2 + Tg**2) &
+ Epsg * Epsdb * FSg_db * StefanBoltzmann * (Td + Tg)*(Td**2 + Tg**2)
hr_md = Epsm * Epsdf * FSm_df * StefanBoltzmann * (Td + Tm)*(Td**2 + Tm**2) &
+ Epsm * Epsdb * FSm_db * StefanBoltzmann * (Td + Tm)*(Td**2 + Tm**2)
RETURN
END SUBROUTINE DL_RES_r2