Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | NL | |||
real(kind=r64), | intent(in) | :: | RHOF(:) | |||
real(kind=r64), | intent(in) | :: | RHOB(:) | |||
real(kind=r64), | intent(in) | :: | TAUF(:) | |||
real(kind=r64), | intent(in) | :: | TAUB(:) | |||
real(kind=r64), | intent(in) | :: | RHO_room | |||
real(kind=r64), | intent(in) | :: | ISOL | |||
real(kind=r64), | intent(out) | :: | QPLUS(0:) | |||
real(kind=r64), | intent(out) | :: | QMINUS(0:) |
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 NETRAD(NL, RHOF, RHOB, TAUF, TAUB, RHO_room, ISOL, QPLUS, QMINUS)
!
! SUBROUTINE INFORMATION:
! AUTHOR JOHN L. WRIGHT
! DATE WRITTEN unknown
! MODIFIED na
!
! RE-ENGINEERED na
! PURPOSE OF THIS SUBROUTINE:
! Returns the solar radiant fluxes between glazing layers
!
!
! METHODOLOGY EMPLOYED:
! Net Radiation Method by LARGELY EDWARDS
! TED, RED, QPLUS, QMINUS correspond to variables found in "Edwards"
! but with reversed layers order indexing (layer 1=outside .. NL=inside)
!
! GAP I is between layer I and I+1
!
! REFERENCES:
! na
!
! USE STATEMENTS:
! na
!
!
IMPLICIT NONE
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: NL ! # of layers, 1=outside .. NL=inside
REAL(r64), INTENT(IN) :: RHOF(:) ! solar reflectance of layer outside facing sides
REAL(r64), INTENT(IN) :: RHOB(:) ! solar reflectance of layer inside facing sides
REAL(r64), INTENT(IN) :: TAUF(:) ! solar transmittance of layer, for incidence
REAL(r64), INTENT(IN) :: TAUB(:) ! solar transmittance of layer, back incidence
REAL(r64), INTENT(IN) :: RHO_room ! effective solar reflectance of room (at inside)
REAL(r64), INTENT(IN) :: ISOL ! incident flux (W/m2)
REAL(r64), INTENT(OUT) :: QPLUS( 0:) ! returned: see Edwards paper
REAL(r64), INTENT(OUT) :: QMINUS( 0:) ! returned: see Edwards paper
!
! SUBROUTINE ARGUMENT DEFINITIONS:
! na
! SUBROUTINE PARAMETER DEFINITIONS:
! na
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) :: TED( NL+1)
REAL(r64) :: RED( NL+1)
INTEGER :: I
! Flow
IF (NL < 1) RETURN
! Reflectance and Transmittance
RED(NL+1) = RHO_room
TED(NL+1) = 0.0d0
!#if 1
DO I=NL,1,-1
TED(I) = TAUF( I) / MAX( 0.00001d0, 1.0d0 - RHOB( I)*RED(I+1))
RED(I) = RHOF(I) + TED( I)*TAUB(I)*RED(I+1)
END DO
!#else
!I = SIZE( RED)
!DO I=NL,1,-1
! RED(I) = RHOF(I) + (TAUF(I)*TAUB(I)*RED(I+1)) &
! / (1.0d0 -(RHOB(I)*RED(I+1)))
! TED(I) = TAUF(I)/(1.0d0 -RHOB(I)*RED(I+1))
!END DO
!#endif
! Outward and Inward Solar Fluxes, QPLUS AND QMINUS, Respectively
QMINUS(0)=ISOL
QPLUS(0)=QMINUS(0)*RED(1)
DO I=1,NL
QMINUS(I) = QMINUS(I-1)*TED(I)
QPLUS(I) = QMINUS(I)*RED(I+1)
END DO
RETURN
END SUBROUTINE NETRAD