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 FM_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 solar optical properties of a fabric for beam radiation incident
! on the forward facingsurface using optical properties at normal incidence and
! 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 ! incidence angle, radians (0 - PI/2)
REAL(r64), INTENT(IN):: RHO_BT0 ! fabric beam-total reflectance
REAL(r64), INTENT(IN):: TAU_BT0 ! fabric beam-total transmittance at normal incidence
! TAU_BTO = TAU_BB0 + TAU_BD0
REAL(r64), INTENT(IN):: TAU_BB0 ! fabric beam-beam transmittance at normal incidence
! = openness
REAL(r64), INTENT(OUT):: RHO_BD ! returned: fabric beam-diffuse reflectance
REAL(r64), INTENT(OUT):: TAU_BB ! returned: fabric beam-beam transmittance
REAL(r64), INTENT(OUT):: TAU_BD ! returned: fabric beam-diffuse transmittance
!
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: THETA ! working incident angle, radians
REAL(r64) :: COSTHETA ! cosine( theta)
REAL(r64) :: R, B ! working temps
REAL(r64) :: RHO_Y ! apparent yarn reflectance
REAL(r64) :: RHO_BT90 ! beam-total reflectance at 90 deg incidence
REAL(r64) :: TAU_BT ! beam-total transmittance
! Flow
THETA = ABS( MAX( -89.99d0*DegToRadians, MIN( 89.99d0*DegToRadians, xTHETA)))
! limit -89.99 - +89.99
! by symmetry, optical properties same at +/- theta
COSTHETA = COS( THETA)
RHO_Y = RHO_BT0/MAX( 0.00001d0, 1.d0 - TAU_BB0)
R = 0.7d0 * RHO_Y**0.7d0
RHO_BT90 = RHO_BT0 + (1.d0 - RHO_BT0)*R
B = 0.6d0
RHO_BD = P01( RHO_BT0 + (RHO_BT90 - RHO_BT0) * (1.d0 - COSTHETA**B), "FM_BEAM RhoBD")
IF (TAU_BT0 < 0.00001d0) THEN
TAU_BB = 0.0d0
TAU_BD = 0.0d0
ELSE
B = MAX( -0.5d0 * LOG( MAX( TAU_BB0, 0.01d0)), 0.35d0)
TAU_BB = TAU_BB0 * COSTHETA**B
B = MAX( -0.5d0 * LOG( MAX( TAU_BT0, .01d0)), 0.35d0)
TAU_BT = TAU_BT0 * COSTHETA**B
TAU_BD = P01( TAU_BT - TAU_BB, "FM_BEAM TauBD")
END IF
RETURN
END SUBROUTINE FM_BEAM