Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | S | |||
real(kind=r64), | intent(in) | :: | W | |||
real(kind=r64), | intent(in) | :: | OMEGA | |||
real(kind=r64), | intent(in) | :: | DE | |||
real(kind=r64), | intent(in) | :: | PHI | |||
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_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.
SUBROUTINE VB_SOL4(S, W, OMEGA, DE, PHI, RHODFS_SLAT, RHOUFS_SLAT, &
TAU_SLAT, RHO_BD, 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 surface Flat-Plate Model with slat transmittance
!
! 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 width (any length units; same units as S)
! must be > 0
REAL(r64), INTENT (IN) :: OMEGA ! incident beam profile angle (radians)
! ltyVBHOR: +=above horizontal
! ltyVBVER: +=clockwise when viewed from above
REAL(r64), INTENT (IN) :: 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), INTENT( IN) :: PHI ! 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) :: RHODFS_SLAT ! solar reflectance downward-facing slat surfaces (concave?)
REAL(r64), INTENT (IN) :: RHOUFS_SLAT ! solar reflectance upward-facing slat surfaces (convex?)
REAL(r64), INTENT (IN) :: TAU_SLAT ! solar transmittance of slat
! Note: all solar slat properties - incident-to-diffuse
REAL(r64), INTENT (OUT) :: RHO_BD ! returned: solar beam-to-diffuse reflectance the venetian blind (front side)
REAL(r64), INTENT (OUT) :: TAU_BD ! returned: solar beam-to-diffuse transmittance of the venetian blind (front side)
!
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: AF, CD ! lengths of diagonal strings used in the four-surface model
REAL(r64) :: F13, F14, F23, F24, F34, F43 ! Shape factors
REAL(r64) :: Z3, Z4 ! diffuse source terms from surfaces 3 and 4 due to incident beam radiation
REAL(r64) :: J3, J4 ! radiosity, surface i
REAL(r64) :: B3, B4, C3, C4 ! temporaries
! flow
AF = SQRT ((W*COS(PHI))**2 + (S - W*SIN(PHI))**2)
CD = SQRT ((W*COS(PHI))**2 + (S + W*SIN(PHI))**2)
!
! CHECK TO SEE WHICH SIDE OF SLAT IS SUNLIT
IF((PHI + OMEGA) >= 0.d0) THEN ! SUN SHINES ON TOP OF SLAT
Z3 = TAU_SLAT*S/DE
Z4 = RHOUFS_SLAT*S/DE
! PRINT *, PHI, OMEGA, DE, 'TOPLIT'
ELSE ! SUN SHINES ON BOTTOM OF SLAT
Z3 = RHODFS_SLAT*S/DE
Z4 = TAU_SLAT*S/DE
! PRINT *, PHI, OMEGA, DE, 'BOTLIT'
ENDIF
!
! CHECK TO SEE IF VENETIAN BLIND IS CLOSED
IF( ABS(PHI - PiOvr2) < SMALL_ERROR ) THEN !VENETIAN BLIND IS CLOSED
! CHECK TO SEE IF THERE ARE GAPS IN BETWEEN SLATS WHEN THE BLIND IS CLOSED
IF(W < S) THEN !YES, THERE ARE GAPS IN BETWEEN SLATS
RHO_BD = (W/S)*RHOUFS_SLAT
TAU_BD = (W/S)*TAU_SLAT
ELSE ! NO, THERE ARE NO GAPS IN BETWEEN SLATS
RHO_BD = RHOUFS_SLAT
TAU_BD = TAU_SLAT
ENDIF ! END OF CHECK FOR GAPS IN BETWEEN SLATS
ELSE ! VENETIAN BLIND IS OPENED
F13 = (S+W-CD)/(2.d0*S)
F14 = (S+W-AF)/(2.d0*S)
F23 = (S+W-AF)/(2.d0*S)
F24 = (S+W-CD)/(2.d0*S)
F34 = (CD+AF-2.d0*S)/(2.d0*W)
F43 = (CD+AF-2.d0*S)/(2.d0*W)
C3 = 1.d0 / (1.d0 - TAU_SLAT*F43)
B3 = (RHODFS_SLAT*F34) / (1.d0 - TAU_SLAT*F43)
C4 = 1.d0 / (1.d0 - TAU_SLAT*F34)
B4 = (RHOUFS_SLAT*F43) / (1.d0 - TAU_SLAT*F34)
J3 = (C3*Z3 + B3*C4*Z4) / (1.d0 - B3*B4)
J4 = (C4*Z4 + B4*C3*Z3) / (1.d0 - B3*B4)
RHO_BD = F13*J3 + F14*J4
TAU_BD = F23*J3 + F24*J4
ENDIF ! END OF CHECK FOR CLOSED BLIND
RETURN
END SUBROUTINE VB_SOL4