Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | DayOfYear | |||
real(kind=r64), | intent(out) | :: | A | |||
real(kind=r64), | intent(out) | :: | B | |||
real(kind=r64), | intent(out) | :: | C | |||
real(kind=r64), | intent(out) | :: | AnnVarSolConstant | |||
real(kind=r64), | intent(out) | :: | EquationOfTime | |||
real(kind=r64), | intent(out) | :: | SineSolarDeclination | |||
real(kind=r64), | intent(out) | :: | CosineSolarDeclination |
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 CalculateDailySolarCoeffs(DayOfYear,A,B,C,AnnVarSolConstant,EquationOfTime,SineSolarDeclination,CosineSolarDeclination)
! SUBROUTINE INFORMATION:
! AUTHOR George Walton
! DATE WRITTEN May 1985
! MODIFIED 1999 for EnergyPlus
! RE-ENGINEERED 2001; LKL; Remove need for English -> SI conversion
! Implement Tarp "fix" for Southern Hemisphere
! PURPOSE OF THIS SUBROUTINE:
! This subroutine computes the daily solar coefficients used in other
! calculations. Specifically, this routine computes values of the solar declination, equation
! of time, and ashrae sky coefficients a, b, and c for a given
! day of the year.
! METHODOLOGY EMPLOYED:
! The method is the same as that recommended in the ASHRAE loads
! algorithms manual, except that the fourier series expressions
! have been extended by two terms for greater accuracy.
! coefficients for the new expressions were determined at USACERL
! using data from the cited references.
! REFERENCES:
! J. L. Threlkeld, "Thermal Environmental Engineering", 1970,
! p.316, for declination and equation of time.
! "ASHRAE Handbook of Fundamentals", 1972, p.387 for sky
! coefficients a, b, and c.
! See SUN3 in SolarShading. See SUN2 in BLAST. See SUN3 in Tarp.
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: DayOfYear ! Day of year (1 - 366)
REAL(r64), INTENT(OUT) :: A ! ASHRAE "A" - Apparent solar irradiation at air mass = 0 [W/M**2]
REAL(r64), INTENT(OUT) :: B ! ASHRAE "B" - Atmospheric extinction coefficient
REAL(r64), INTENT(OUT) :: C ! ASHRAE "C" - Diffuse radiation factor
REAL(r64), INTENT(OUT) :: AnnVarSolConstant ! Annual variation in the solar constant
REAL(r64), INTENT(OUT) :: EquationOfTime ! Equation of Time
REAL(r64), INTENT(OUT) :: SineSolarDeclination ! Sine of Solar Declination
REAL(r64), INTENT(OUT) :: CosineSolarDeclination ! Cosine of Solar Declination
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER :: DayCorrection=PI*2.d0/366.d0
REAL(r64), PARAMETER, DIMENSION(9) :: SineSolDeclCoef = & !Fitted coefficients of Fourier series
(/ .00561800d0, .0657911d0, -.392779d0, .00064440d0,-.00618495d0, & ! Sine of declination coefficients
-.00010101d0,-.00007951d0,-.00011691d0, .00002096d0 /)
REAL(r64), PARAMETER, DIMENSION(9) :: EqOfTimeCoef = & !Fitted coefficients of Fourier Series
(/ .00021971d0,-.122649d0, .00762856d0,-.156308d0, -.0530028d0, & ! Equation of Time coefficients
-.00388702d0,-.00123978d0,-.00270502d0,-.00167992d0 /)
REAL(r64), PARAMETER, DIMENSION(9) :: ASHRAE_A_Coef = & !Fitted coefficients of Fourier Series
(/ 1161.6685d0, 1.1554d0, 77.3575d0, -0.5359d0, -3.7622d0, & ! ASHRAE A Factor coefficients
0.9875d0, -3.3924d0, -1.7445d0, 1.1198d0 /)
! English (original) units:
! 368.49341,.366502,24.538624,-.169983,-1.193417, &
! .313261,-1.076093,-.543376,.355197 , &
REAL(r64), PARAMETER, DIMENSION(9) :: ASHRAE_B_Coef = & !Fitted coefficients of Fourier Series
(/ .171631d0,-.00400448d0,-.0344923d0,.00000209d0,.00325428d0, & ! ASHRAE B Factor coefficients
-.00085429d0,.00229562d0,.0009034d0,-.0011867d0 /)
REAL(r64), PARAMETER, DIMENSION(9) :: ASHRAE_C_Coef = & !Fitted coefficients of Fourier Series
(/ .0905151d0,-.00322522d0,-.0407966d0,.000104164d0,.00745899d0, & ! ASHRAE C Factor coefficients
-.00086461d0,.0013111d0,.000808275d0,-.00170515d0 /)
! INTERFACE BLOCK SPECIFICATIONS:
! na
! DERIVED TYPE DEFINITIONS:
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) X ! Day of Year in Radians (Computed from Input DayOfYear)
REAL(r64) CosX ! COS(X)
REAL(r64) SinX ! SIN(X)
X=DayCorrection*DayOfYear ! Convert Julian date (Day of Year) to angle X
! Calculate sines and cosines of X
SinX = SIN(X)
CosX = COS(X)
SineSolarDeclination = SineSolDeclCoef(1) + &
SineSolDeclCoef(2)*SinX + &
SineSolDeclCoef(3)*CosX + &
SineSolDeclCoef(4)*(SinX*CosX*2.0d0) + &
SineSolDeclCoef(5)*(CosX**2 - SinX**2) + &
SineSolDeclCoef(6)*(SinX*(CosX**2 - SinX**2) + CosX*(SinX*CosX*2.0d0)) + &
SineSolDeclCoef(7)*(CosX*(CosX**2 - SinX**2) - SinX*(SinX*CosX*2.0d0)) + &
SineSolDeclCoef(8)*(2.0d0*(SinX*CosX*2.0d0)*(CosX**2 - SinX**2)) + &
SineSolDeclCoef(9)*((CosX**2 - SinX**2)**2 - (SinX*CosX*2.0d0)**2)
CosineSolarDeclination=SQRT(1.0-SineSolarDeclination**2)
EquationOfTime = EqOfTimeCoef(1) + &
EqOfTimeCoef(2)*SinX + &
EqOfTimeCoef(3)*CosX + &
EqOfTimeCoef(4)*(SinX*CosX*2.0d0) + &
EqOfTimeCoef(5)*(CosX**2 - SinX**2) + &
EqOfTimeCoef(6)*(SinX*(CosX**2 - SinX**2) + CosX*(SinX*CosX*2.0d0)) + &
EqOfTimeCoef(7)*(CosX*(CosX**2 - SinX**2) - SinX*(SinX*CosX*2.0d0)) + &
EqOfTimeCoef(8)*(2.0d0*(SinX*CosX*2.0d0)*(CosX**2 - SinX**2)) + &
EqOfTimeCoef(9)*((CosX**2 - SinX**2)**2 - (SinX*CosX*2.0d0)**2)
AnnVarSolConstant=1.000047d0 + .000352615d0*SinX + .0334454d0*CosX
A = ASHRAE_A_Coef(1) + &
ASHRAE_A_Coef(2)*SinX + &
ASHRAE_A_Coef(3)*CosX + &
ASHRAE_A_Coef(4)*(SinX*CosX*2.0d0) + &
ASHRAE_A_Coef(5)*(CosX**2 - SinX**2) + &
ASHRAE_A_Coef(6)*(SinX*(CosX**2 - SinX**2) + CosX*(SinX*CosX*2.0d0)) + &
ASHRAE_A_Coef(7)*(CosX*(CosX**2 - SinX**2) - SinX*(SinX*CosX*2.0d0)) + &
ASHRAE_A_Coef(8)*(2.0d0*(SinX*CosX*2.0d0)*(CosX**2 - SinX**2)) + &
ASHRAE_A_Coef(9)*((CosX**2 - SinX**2)**2 - (SinX*CosX*2.0d0)**2)
! Compute B and C coefficients
IF (Latitude < 0.0d0) THEN
! If in southern hemisphere, compute B and C with a six month time shift.
X = X - PI
SinX = SIN(X)
CosX = COS(X)
ENDIF
B = ASHRAE_B_Coef(1) + &
ASHRAE_B_Coef(2)*SinX + &
ASHRAE_B_Coef(3)*CosX + &
ASHRAE_B_Coef(4)*(SinX*CosX*2.0d0) + &
ASHRAE_B_Coef(5)*(CosX**2 - SinX**2) + &
ASHRAE_B_Coef(6)*(SinX*(CosX**2 - SinX**2) + CosX*(SinX*CosX*2.0d0)) + &
ASHRAE_B_Coef(7)*(CosX*(CosX**2 - SinX**2) - SinX*(SinX*CosX*2.0d0)) + &
ASHRAE_B_Coef(8)*(2.0d0*(SinX*CosX*2.0d0)*(CosX**2 - SinX**2)) + &
ASHRAE_B_Coef(9)*((CosX**2 - SinX**2)**2 - (SinX*CosX*2.0d0)**2)
C = ASHRAE_C_Coef(1) + &
ASHRAE_C_Coef(2)*SinX + &
ASHRAE_C_Coef(3)*CosX + &
ASHRAE_C_Coef(4)*(SinX*CosX*2.0d0) + &
ASHRAE_C_Coef(5)*(CosX**2 - SinX**2) + &
ASHRAE_C_Coef(6)*(SinX*(CosX**2 - SinX**2) + CosX*(SinX*CosX*2.0d0)) + &
ASHRAE_C_Coef(7)*(CosX*(CosX**2 - SinX**2) - SinX*(SinX*CosX*2.0d0)) + &
ASHRAE_C_Coef(8)*(2.0d0*(SinX*CosX*2.0d0)*(CosX**2 - SinX**2)) + &
ASHRAE_C_Coef(9)*((CosX**2 - SinX**2)**2 - (SinX*CosX*2.0d0)**2)
RETURN
END SUBROUTINE CalculateDailySolarCoeffs