Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | BlindNum | |||
integer, | intent(in) | :: | Isolvis | |||
real(kind=r64), | intent(in) | :: | c(15) | |||
real(kind=r64), | intent(in) | :: | b_el | |||
real(kind=r64), | intent(out) | :: | p(16) |
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 BlindOpticsDiffuse (BlindNum,ISolVis,c,b_el,p)
! SUBROUTINE INFORMATION:
! AUTHOR Hans Simmler
! DATE WRITTEN July-Aug 1995
! MODIFIED Aug 2001 (FCW): adapt to EnergyPlus
! Aug 2002 (FCW): make corrections so that calculations are consistent with
! G(i) = Sum over j of J(j)*F(j,i). Previously, i,j was
! interchanged in F, so that
! G(i) = Sum over j of J(j)*F(i,j), which is wrong.
! This change was made to resolve discrepancies between EnergyPlus results
! and blind transmittance measurements made at Oklahoma State Univ.
! Feb 2004 (FCW): modify slat edge correction calc to avoid possible divide by zero
!
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! From the slat properties, calculates the diffuse solar, diffuse visible and IR
! transmission and reflection properties of a window blind.
! METHODOLOGY EMPLOYED:
! na
! REFERENCES:
! "Solar-Thermal Window Blind Model for DOE-2," H. Simmler, U. Fischer and
! F. Winkelmann, Lawrence Berkeley National Laboratory, Jan. 1996.
! USE STATEMENTS:na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: BlindNum ! Blind number
INTEGER, INTENT(IN) :: Isolvis ! 1 = solar and IR calculation; 2 = visible calculation
REAL(r64), INTENT(IN) :: c(15) ! Slat properties
REAL(r64), INTENT(IN) :: b_el ! Slat elevation (radians)
REAL(r64), INTENT(OUT) :: p(16) ! Blind properties
! SUBROUTINE PARAMETER DEFINITIONS:na
! INTERFACE BLOCK SPECIFICATIONS:na
! DERIVED TYPE DEFINITIONS:na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) ri,rib ! Front and back IR slat reflectance
REAL(r64) phib ! Elevation of slat normal vector (radians)
REAL(r64) phis ! Source elevation (radians)
REAL(r64) delphis ! Angle increment for integration over source distribution (radians)
REAL(r64) fEdgeSource(10) ! Slat edge correction factor vs source elevation
REAL(r64) fEdgeA(2) ! Average slat edge correction factor for upper and lower quadrants
! seen by window blind
REAL(r64) gamma ! phib - phis
INTEGER Iphis ! Source elevation counter
INTEGER IUpDown ! =1 for source in upper quadrant, =2 for source in lower quadrant
REAL(r64) fEdge,fEdge1 ! Slat edge correction factor
REAL(r64) J(6) ! Slat section radiosity vector
REAL(r64) G(6) ! Slat section irradiance vector
REAL(r64) Q(6) ! Slat section radiance vector
REAL(r64) F(6,6) ! View factor array
REAL(r64) X(4,4) ! Exchange matrix
REAL(r64) Xinv(4,4) ! Inverse of exchange matrix
INTEGER k,m ! Array indices
INTEGER indx(4) ! LU decomposition indices
REAL(r64) BlindIRreflFront ! Blind front IR reflectance
REAL(r64) BlindIRreflBack ! Blind back IR reflectance
! The slat input properties are:
! c(1) 0. (unused)
! c(2) Slat width (m)
! c(3) Slat separation (m)
! c(4) 0. (unused)
! c(5) 0. (unused)
! c(6) 0. (unused)
! The following are solar or visible properties
! c(7) trans beam-diff
! c(8) refl front beam-diff
! c(9) refl back beam-diff
! c(10) trans diff-diff
! c(11) refl front diff-diff
! c(12) refl back diff-diff
! The following are hemispherical thermal IR properties
! c(13) trans diff-diff
! c(14) emiss front diff
! c(15) emiss back diff
! The calculated blind properties are:
! The following are solar or visible properties
! p(1) trans front beam-beam
! p(2) refl front beam-beam
! p(3) trans back beam-beam
! p(4) refl back beam-beam
! p(5) trans front beam-diff
! p(6) refl front beam-diff
! p(7) trans back beam-diff
! p(8) refl back beam-diff
! p(9) trans front diff-diff
! p(10) refl front diff-diff
! p(11) trans back diff-diff
! p(12) refl back diff-diff
! The following are IR properties
! p(13) IR trans front (same as IR trans back)
! p(14) IR emissivity front
! p(15) IR emissivity back
! p(16) 0.0 (unused)
! Calculate view factors between slat sections (slat is divided longitudinally into two equal parts)
CALL VIEWFAC(c(2),c(3),b_el,PiOvr2,F)
! Set up exchange matrix X for diffuse properties
do k=3,5,2
do m=3,6
X(k-2,m-2)=-c(12)*F(m,k)-c(10)*F(m,k+1)
X(k-1,m-2)=-c(10)*F(m,k)-c(11)*F(m,k+1)
end do
end do
do k=1,4
X(k,k)=X(k,k)+1.0d0
end do
indx = 0
CALL InvertMatrix(X,Xinv,indx,4,4) !Objexx:Note X modified by this call
!---------Calculate diffuse short-wave properties for the front side of the blind
! Sources
Q(3) = c(12)*F(1,3) + c(10)*F(1,4)
Q(4) = c(10)*F(1,3) + c(11)*F(1,4)
Q(5) = c(12)*F(1,5) + c(10)*F(1,6)
Q(6) = c(10)*F(1,5) + c(11)*F(1,6)
! Radiosities
J(1)=1.0d0
J(2)=0.0d0
do k=3,6
J(k)=0.0d0
do m=3,6
J(k)=J(k)+Xinv(k-2,m-2)*Q(m)
end do
end do
! Irradiances
do k=1,6
G(k)=0.0d0
do m=1,6
!G(k)=G(k)+F(k,m)*J(m)
G(k)=G(k)+J(m)*F(m,k)
end do
end do
! Slat edge correction factor
phib = b_el
delphis = PiOvr2/10.d0
DO IUpDown = 1,2
DO Iphis = 1,10
phis = -(iphis-0.5d0)*delphis
IF(IUpDown == 2) phis = (iphis-0.5d0)*delphis
fEdgeSource(Iphis) = 0.0d0
fEdge1 = 0.0d0
gamma = phib - phis
IF(ABS(SIN(gamma))>0.01d0) THEN
IF((phib > 0.0 .AND. phib <= PiOvr2 .AND. phis <= phib) .OR. &
(phib > PiOvr2 .AND. phib <= Pi .AND. phis > -(Pi-phib))) &
fEdge1 = Blind(BlindNum)%SlatThickness * ABS(SIN(gamma)) / &
((Blind(BlindNum)%SlatSeparation + Blind(BlindNum)%SlatThickness/ABS(SIN(phib)))*COS(phis))
fEdgeSource(Iphis) = MIN(1.0d0,ABS(fEdge1))
END IF
END DO
fEdgeA(IUpDown) = DiffuseAverage(fEdgeSource)
END DO
fEdge = 0.5d0*(fEdgeA(1) + fEdgeA(2))
! Front diffuse-diffuse transmittance (transmittance of slat edge assumed zero)
p(9) = G(2)*(1.0d0-fEdge)
! Front diffuse-diffuse reflectance (edge of slat is assumed to have same diffuse
! reflectance as front side of slat, c(11))
p(10) = G(1)*(1.0d0-fEdge) + fEdge*C(11)
!-----------Calculate diffuse short-wave properties for the back side of the blind
! Sources
Q(3)=c(12)*F(2,3)+c(10)*F(2,4)
Q(4)=c(10)*F(2,3)+c(11)*F(2,4)
Q(5)=c(12)*F(2,5)+c(10)*F(2,6)
Q(6)=c(10)*F(2,5)+c(11)*F(2,6)
! Radiosities
J(1)=0.0d0
J(2)=1.0d0
do k=3,6
J(k)=0.0d0
do m=3,6
J(k)=J(k)+Xinv(k-2,m-2)*Q(m)
end do
end do
! Irradiances
do k=1,6
G(k)=0.0d0
do m=1,6
!G(k)=G(k)+F(k,m)*J(m)
G(k)=G(k)+J(m)*F(m,k)
end do
end do
! Back diffuse-diffuse transmittance
p(11)=G(1)*(1.0d0-fEdge)
! Back hemi-hemi reflectance
p(12)=G(2)*(1.0d0-fEdge) + fEdge*C(11)
IF(ISolVis == 1) THEN
!-----------Calculate IR properties of the blind
! (use same set of view factors as for diffuse short-wave properties)
! Front and back slat IR reflectances
ri =1-c(13)-c(14)
rib=1-c(13)-c(15)
! Set up exchange matrix X for diffuse properties
do k=3,5,2
do m=3,6
X(k-2,m-2)=-rib *F(m,k) -c(13)*F(m,k+1)
X(k-1,m-2)=-c(13)*F(m,k) -ri *F(m,k+1)
end do
end do
do k=1,4
X(k,k)=X(k,k)+1.0d0
end do
indx = 0
CALL InvertMatrix(X,Xinv,indx,4,4) !Objexx: Note X modified by this call
!---------Calculate diffuse IR properties for the FRONT side of the blind
! Sources
Q(3) = rib *F(1,3) + c(13)*F(1,4)
Q(4) = c(13)*F(1,3) + ri *F(1,4)
Q(5) = rib *F(1,5) + c(13)*F(1,6)
Q(6) = c(13)*F(1,5) + ri *F(1,6)
! Radiosities
J(1)=1.0d0
J(2)=0.0d0
do k=3,6
J(k)=0.0d0
do m=3,6
J(k)=J(k)+Xinv(k-2,m-2)*Q(m)
end do
end do
! Irradiances
do k=1,6
G(k)=0.0d0
do m=1,6
!G(k)=G(k)+F(k,m)*J(m)
G(k)=G(k)+J(m)*F(m,k)
end do
end do
! Front diffuse-diffuse IR transmittance (transmittance of slat edge assumed zero)
p(13) = G(2)*(1.d0-fEdge)
! Front diffuse-diffuse IR reflectance (edge of slat is assumed to have same IR
! reflectance as front side of slat, ri)
BlindIRreflFront = G(1)*(1.d0-fEdge) + fEdge*ri
! Front IR emissivity
p(14) = MAX(0.0001d0,1.0d0-p(13)-BlindIRreflFront)
!-----------Calculate diffuse IR properties for the BACK side of the blind
! Sources
Q(3)= rib *F(2,3) + c(13)*F(2,4)
Q(4)= c(13)*F(2,3) + ri *F(2,4)
Q(5)= rib *F(2,5) + c(13)*F(2,6)
Q(6)= c(13)*F(2,5) + ri *F(2,6)
! Radiosities
J(1)=0.0d0
J(2)=1.0d0
do k=3,6
J(k)=0.0d0
do m=3,6
J(k)=J(k)+Xinv(k-2,m-2)*Q(m)
end do
end do
! Irradiances
do k=1,6
G(k)=0.0d0
do m=1,6
!G(k)=G(k)+F(k,m)*J(m)
G(k)=G(k)+J(m)*F(m,k)
end do
end do
! Back diffuse-diffuse IR reflectance
BlindIRreflBack = G(2)*(1.d0-fEdge) + fEdge*ri
! Back IR emissivity
p(15) = MAX(0.0001d0,1.0d0-p(13)-BlindIRreflBack)
END IF ! End of IR properties calculation
RETURN
END SUBROUTINE BlindOpticsDiffuse