Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | S | |||
real(kind=r64), | intent(in) | :: | W | |||
real(kind=r64), | intent(in) | :: | SL_WR | |||
real(kind=r64), | intent(in) | :: | PHIx | |||
real(kind=r64), | intent(in) | :: | OMEGAx | |||
real(kind=r64), | intent(in) | :: | RHODFS_SLAT | |||
real(kind=r64), | intent(in) | :: | RHOUFS_SLAT | |||
real(kind=r64), | intent(in) | :: | TAU_SLAT | |||
real(kind=r64), | intent(out) | :: | RHO_BD | |||
real(kind=r64), | intent(out) | :: | TAU_BB | |||
real(kind=r64), | intent(out) | :: | TAU_BD |
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 VB_SOL46_CURVE(S, W, SL_WR, PHIx, OMEGAx, RHODFS_SLAT, RHOUFS_SLAT, &
TAU_SLAT, RHO_BD, TAU_BB, TAU_BD)
! 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:
! Calculates the venetian blind layer effective solar transmittance and reflectance.
!
! METHODOLOGY EMPLOYED:
! Four and six surface curve-slat model with slat transmittance. For back side
! reflectance call this routine a second time with the same input data - except
! negative the slat angle, PHI_DEG.
!
! REFERENCES:
! na
! USE STATEMENTS:
! na
!
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
REAL(r64), INTENT(IN):: S ! slat spacing (any length units; same units as W)
! must be > 0
REAL(r64), INTENT(IN):: W ! slat tip-to-tip (chord) width (any length units; same units as S)
! must be > 0
REAL(r64), INTENT(IN):: SL_WR ! slat curvature radius ratio (= W/R)
! 0 = flat
REAL(r64), INTENT(IN):: PHIx ! slat angle, radians (-PI/2 <= PHI <= PI/2)
! ltyVBHOR: + = front-side slat tip below horizontal
! ltyVBVER: + = front-side slat tip is counter-
! clockwise from normal (viewed from above)
REAL(r64), INTENT(IN):: OMEGAx ! incident beam profile angle (radians)
! ltyVBHOR: +=above horizontal
! ltyVBVER: +=clockwise when viewed from above
! Note: All solar slat properties are incident-to-diffuse
! Specular effects not covered by model
REAL(r64), INTENT(IN):: RHODFS_SLAT ! SW (solar) reflectance downward-facing slat surfaces (concave?)
REAL(r64), INTENT(IN):: RHOUFS_SLAT ! SW (solar) reflectance upward-facing slat surfaces (convex?)
REAL(r64), INTENT(IN):: TAU_SLAT ! SW (solar) transmittance of slats
REAL(r64), INTENT(OUT):: RHO_BD ! returned: effective SW (solar) beam-to-diffuse reflectance front side
REAL(r64), INTENT(OUT):: TAU_BB ! returned: effective SW (solar) beam-to-beam transmittance front side
REAL(r64), INTENT(OUT):: TAU_BD ! returned: effective SW (solar) beam-to-diffuse transmittance front side
!
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: DE ! distance from front tip of any slat to shadow (caused by the adjacent slat) on
! the plane of the same slat; DE may be greater than the slat width, W
REAL(r64) :: PHI
REAL(r64) :: OMEGA
REAL(r64) :: SL_RAD,SL_THETA,Slope,T_CORR_D,T_CORR_F,RHO_TEMP,TAU_TEMP
REAL(r64) :: XA,XB,XC,XD,XE,XF,YA,YB,YC,YD,YE,YF
INTEGER :: CORR
! Flow
DE = 0.0d0 ! INITIALIZE DE
CORR=1
! limit slat angle to +/- 90 deg
PHI = MAX( -DegToRadians*90.0d0, MIN( DegToRadians*90.0d0, PHIx))
! limit profile angle to +/- 89.5 deg
OMEGA = MAX( -DegToRadians*89.5d0, MIN( DegToRadians*89.5d0, OMEGAx))
SL_RAD = W / MAX( SL_WR, 0.0000001d0)
SL_THETA = 2.d0 * ASIN( 0.5d0*SL_WR)
IF (CORR>0) THEN ! CORRECT FOR SLAT CURVATURE BY SETTING CORR = 1
! DETERMINE BOUNDS FOR CURVATURE CORRECTION AND APPLY CORRECTION TO BEAM-BEAM TRANSMITTANCE
IF( ABS(PHI+OMEGA) < SL_THETA/2.d0) THEN
! CALCULATE BEAM TRANSMISSION
XA=SL_RAD*SIN(-SL_THETA/2.d0) !Glass-side end coordinate
YA=SL_RAD*COS(-SL_THETA/2.d0)
XB=-XA !Indoor-side end coordinate
YB=YA
YC=SL_RAD*COS(PHI+OMEGA) !Tangent to slat in irradiance direction
XC=SQRT(SL_RAD**2-YC**2)
Slope=-XC/YC
IF (ABS(Slope) < SMALL_ERROR) THEN
XD=0.0d0
YD=YA
XE=0.0d0
YE=YD
ELSE
IF ((PHI+OMEGA) < 0.0d0) THEN
XC=-XC
Slope=-Slope
XD=(YB-Slope*XB)/(-1.d0/Slope-Slope)
XF=(YA-Slope*XA)/(-1.d0/Slope-Slope)
XE=XA+2.d0*ABS(XA-XF)
ELSE
XD=(YA-Slope*XA)/(-1.d0/Slope-Slope)
XF=(YB-Slope*XB)/(-1.d0/Slope-Slope)
XE=XB-2.d0*ABS(XB-XF)
ENDIF
YD=-XD/Slope
YE=-XE/Slope
YF=-XF/Slope
ENDIF
T_CORR_D=SQRT((XC-XD)**2+(YC-YD)**2) !Slat thickness perpendicular to light direction
T_CORR_F=SQRT((XC-XF)**2+(YC-YF)**2)
TAU_BB=1.0d0 - T_CORR_D/(S*COS(OMEGA))
ELSE
! DO NOT APPLY CURVATURE CORRECTION TO BEAM-BEAM TRANSMITTANCE
IF (ABS( OMEGA + PHI) < 0.0001d0) THEN
DE = S*1000000.0d0
ELSE
DE = S * ABS(COS(OMEGA) / SIN(OMEGA + PHI))
ENDIF
! CHECK TO SEE IF THERE IS DIRECT BEAM TRANSMISSION
IF ((DE/W) > (1.0d0 - SMALL_ERROR)) THEN ! YES
TAU_BB = MAX( 0.d0, (DE-W)/DE)
ELSE ! NO
TAU_BB = 0.0d0
ENDIF
ENDIF
! CHECK TO SEE IF CURVATURE CORRECTION INCLUDES DOUBLE BLOCKAGE
! (TAU_BB < 0.0 AND SET TAU_BB = 0.0)
IF (TAU_BB < 0.0d0) THEN ! YES, THERE IS DOUBLE BLOCKAGE
TAU_BB = 0.0d0
! DO NOT APPLY CURVATURE CORRECTION TO RHO_BD, TAU_BD IF TAU_BB < 0.0
IF (ABS( OMEGA + PHI) < 0.0001d0) THEN
DE = S*1000000.0d0
ELSE
DE = S * ABS(COS(OMEGA) / SIN(OMEGA + PHI))
ENDIF
IF((DE/W) > (1.0d0 - SMALL_ERROR)) THEN ! YES
CALL VB_SOL4(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
ELSE ! NO
CALL VB_SOL6(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
ENDIF
ELSE ! NO, THERE IS NO DOUBLE BLOCKAGE
IF(ABS(PHI+OMEGA)<(SL_THETA/2.d0)) THEN ! YES, APPLY CURVATURE CORRECTION
XA=SL_RAD*SIN(-SL_THETA/2.d0) !Glass-side end coordinate
YA=SL_RAD*COS(-SL_THETA/2.d0)
XB=-XA !Indoor-side end coordinate
YB=YA
YC=SL_RAD*COS(PHI+OMEGA) !Tangent to slat in irradiance direction
XC=SQRT(SL_RAD**2-YC**2)
Slope=-XC/YC
IF (ABS(Slope) < SMALL_ERROR) THEN
XD=0.0d0
YD=YA
XE=0.0d0
YE=YD
ELSE
IF ((PHI+OMEGA) < 0.d0) THEN
XC=-XC
Slope=-Slope
XD=(YB-Slope*XB)/(-1.d0/Slope-Slope)
XF=(YA-Slope*XA)/(-1.d0/Slope-Slope)
XE=XA+2.0d0*ABS(XA-XF)
ELSE
XD=(YA-Slope*XA)/(-1.d0/Slope-Slope)
XF=(YB-Slope*XB)/(-1.d0/Slope-Slope)
XE=XB-2.d0*ABS(XB-XF)
ENDIF
YD=-XD/Slope
YE=-XE/Slope
YF=-XF/Slope
ENDIF
T_CORR_D=SQRT((XC-XD)**2+(YC-YD)**2) ! Slat thickness perpendicular to light direction
T_CORR_F=SQRT((XC-XF)**2+(YC-YF)**2)
IF ((PHI+OMEGA)>= 0.0d0) THEN ! Slat is lit from above
DE=XC-XA
CALL VB_SOL6(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
RHO_BD=RHO_BD*T_CORR_D/(S*COS(OMEGA))
TAU_BD=TAU_BD*T_CORR_D/(S*COS(OMEGA))
ELSE ! Slat is lit from below
DE=XC-XA
CALL VB_SOL6(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
RHO_TEMP=RHO_BD*T_CORR_F/(S*COS(OMEGA))
TAU_TEMP=TAU_BD*T_CORR_F/(S*COS(OMEGA))
DE=ABS(XB-XF)
CALL VB_SOL6(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
RHO_BD=RHO_BD*(T_CORR_D-T_CORR_F)/(S*COS(OMEGA))+RHO_TEMP
TAU_BD=TAU_BD*(T_CORR_D-T_CORR_F)/(S*COS(OMEGA))+TAU_TEMP
ENDIF
ELSE ! NO, DO NOT APPLY CURVATURE CORRECTION
IF (ABS( OMEGA + PHI) < 0.0001d0) THEN
DE = S*1000000.0d0
ELSE
DE = S * ABS(COS(OMEGA) / SIN(OMEGA + PHI))
ENDIF
IF((DE/W) > (1.0d0 - SMALL_ERROR)) THEN ! YES
CALL VB_SOL4(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
ELSE ! NO
CALL VB_SOL6(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
ENDIF
ENDIF
ENDIF
ELSE ! DO NOT CORRECT FOR SLAT CURVATURE
! CHECK TO SEE IF BEAM IS ALLIGNED WITH SLATS
IF(ABS(PHI + OMEGA) < SMALL_ERROR) THEN ! YES!
RHO_BD = 0.0d0
TAU_BB = 1.0d0
TAU_BD = 0.0d0
ELSE ! BEAM NOT ALIGNED WITH SLATS
RHO_BD = 0.0d0
TAU_BB = 0.0d0
TAU_BD = 0.0d0
DE = S * ABS(COS(OMEGA) / SIN(OMEGA + PHI))
! CHECK TO SEE IF THERE IS DIRECT BEAM TRANSMISSION
IF((DE/W) > (1.0d0 - SMALL_ERROR)) THEN ! YES
TAU_BB = (DE-W)/DE
IF(TAU_BB < 0.d0) TAU_BB = 0.0d0
CALL VB_SOL4(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
ELSE ! NO
TAU_BB = 0.0d0
CALL VB_SOL6(S, W, OMEGA, DE, PHI, &
RHODFS_SLAT, RHOUFS_SLAT, TAU_SLAT, &
RHO_BD, TAU_BD)
ENDIF ! END CHECK FOR DIRECT BEAM TRANSMISSION
ENDIF ! END CHECK TO SEE IF BEAM ALLIGNED WITH SLATS
ENDIF
RETURN
END SUBROUTINE VB_SOL46_CURVE