Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=r64), | intent(in) | :: | xTHETA | |||
real(kind=r64), | intent(in) | :: | RHO_BT0 | |||
real(kind=r64), | intent(in) | :: | TAU_BT0 | |||
real(kind=r64), | intent(in) | :: | TAU_BB0 | |||
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 RB_BEAM(xTHETA, RHO_BT0, TAU_BT0, TAU_BB0, 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 roller blind off-normal properties using semi-empirical relations
!
!
! 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):: xTHETA ! angle of incidence, radians (0 - PI/2)
REAL(r64), INTENT(IN):: RHO_BT0 ! normal incidence beam-total front reflectance
REAL(r64), INTENT(IN):: TAU_BT0 ! normal incidence beam-total transmittance
! TAU_BT0 = TAU_BB0 + TAU_BD0
REAL(r64), INTENT(IN):: TAU_BB0 ! normal incidence beam-beam transmittance
! (openness)
REAL(r64), INTENT(OUT):: RHO_BD ! returned: beam-diffuse front reflectance
REAL(r64), INTENT(OUT):: TAU_BB ! returned: beam-beam transmittance
REAL(r64), INTENT(OUT):: TAU_BD ! returned: beam-diffuse transmittance
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: THETA ! working angle of incidence (limited < 90 deg)
REAL(r64) :: TAUM0 ! apparent blind material transmittance at normal incidence
REAL(r64) :: THETA_CUTOFF ! cutoff angle, radians (angle beyond which total transmittance goes to zero)
REAL(r64) :: TAUBT_EXPO ! exponent in the beam-total transmittance model
REAL(r64) :: TAUBB_EXPO ! exponent in the beam-beam transmittance model
REAL(r64) :: TAU_BT ! beam-total transmittance
! Flow
THETA = MIN( 89.99d0 * DegToRadians, xTHETA)
IF (TAU_BB0 > 0.9999d0) THEN
TAU_BB = 1.0d0
TAU_BT = 1.0d0
ELSE
! beam total
TAUM0 = MIN( 1.0d0, (TAU_BT0 - TAU_BB0) / (1.0d0-TAU_BB0))
IF (TAUM0 <= 0.33d0) THEN
TAUBT_EXPO = 0.133d0 * (TAUM0 + 0.003d0)**(-0.467d0)
ELSE
TAUBT_EXPO = 0.33d0 * (1.0d0 - TAUM0)
ENDIF
TAU_BT = TAU_BT0 * COS( THETA)**TAUBT_EXPO ! always 0 - 1
THETA_CUTOFF = DegToRadians*(90.d0 - 25.d0 * COS( TAU_BB0 * PiOvr2))
IF (THETA >= THETA_CUTOFF) THEN
TAU_BB = 0.0d0
ELSE
TAUBB_EXPO = 0.6d0 * COS( TAU_BB0 * PiOvr2)**0.3d0
TAU_BB = TAU_BB0 * COS( PiOvr2*THETA/THETA_CUTOFF)**TAUBB_EXPO
! BB correlation can produce results slightly larger than BT
! Enforce consistency
TAU_BB = MIN( TAU_BT, TAU_BB)
END IF
END IF
RHO_BD = RHO_BT0
TAU_BD = P01( TAU_BT-TAU_BB, "RB_BEAM TauBD")
RETURN
END SUBROUTINE RB_BEAM