Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | JulianDayOfYear | |||
real(kind=r64), | intent(out) | :: | SineOfSolarDeclination | |||
real(kind=r64), | intent(out) | :: | EquationOfTime |
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 SUN3(JulianDayOfYear,SineOfSolarDeclination,EquationOfTime)
! SUBROUTINE INFORMATION:
! AUTHOR Legacy Code
! DATE WRITTEN
! MODIFIED na
! RE-ENGINEERED Linda K. Lawrie
! PURPOSE OF THIS SUBROUTINE:
! This subroutine computes the coefficients for determining
! the solar position.
! METHODOLOGY EMPLOYED:
! The expressions are based on least-squares fits of data on p.316 of 'Thermal
! Environmental Engineering' by Threlkeld and on p.387 of the ASHRAE Handbook
! of Fundamentals (need date of ASHRAE HOF).
! REFERENCES:
! BLAST/IBLAST code, original author George Walton
! USE STATEMENTS:
! na
IMPLICIT NONE ! Enforce explicit typing of all variables in this routine
! SUBROUTINE ARGUMENT DEFINITIONS:
INTEGER, INTENT(IN) :: JulianDayOfYear ! Julian Day Of Year
REAL(r64), INTENT(OUT) :: SineOfSolarDeclination ! Sine of Solar Declination
REAL(r64), INTENT(OUT) :: EquationOfTime ! Equation of Time (Degrees)
! SUBROUTINE PARAMETER DEFINITIONS:
REAL(r64), PARAMETER, DIMENSION(9) :: SineSolDeclCoef = & !Fitted coefficients of Fourier series
(/ .00561800d0, .0657911d0, -.392779d0, .00064440d0,-.00618495d0, & ! SINE OF DECLINATION
-.00010101d0,-.00007951d0,-.00011691d0, .00002096d0/) ! COEFFICIENTS
REAL(r64), PARAMETER, DIMENSION(9) :: EqOfTimeCoef = & !Fitted coefficients of Fourier Series
(/ .00021971d0,-.122649d0, .00762856d0,-.156308d0, -.0530028d0, & ! EQUATION OF TIME
-.00388702d0,-.00123978d0,-.00270502d0,-.00167992d0/) ! COEFFICIENTS
! INTERFACE BLOCK SPECIFICATIONS
! na
! DERIVED TYPE DEFINITIONS
! na
! SUBROUTINE LOCAL VARIABLE DECLARATIONS:
REAL(r64) X ! Day of Year in Radians (Computed from Input JulianDayOfYear)
REAL(r64) COSX ! COS(X)
REAL(r64) SineX ! SIN(X)
X = .017167d0 * JulianDayOfYear ! Convert julian date to angle X
! Calculate sines and cosines of X
SineX = SIN(X)
CosX = COS(X)
SineOfSolarDeclination = SineSolDeclCoef(1) + &
SineSolDeclCoef(2)*SineX + &
SineSolDeclCoef(3)*CosX + &
SineSolDeclCoef(4)*(SineX*CosX*2.d0) + &
SineSolDeclCoef(5)*(CosX**2 - SineX**2) + &
SineSolDeclCoef(6)*(SineX*(CosX**2 - SineX**2) + CosX*(SineX*CosX*2.d0)) + &
SineSolDeclCoef(7)*(CosX*(CosX**2 - SineX**2) - SineX*(SineX*CosX*2.d0)) + &
SineSolDeclCoef(8)*(2.d0*(SineX*CosX*2.d0)*(CosX**2 - SineX**2)) + &
SineSolDeclCoef(9)*((CosX**2 - SineX**2)**2 - (SineX*CosX*2.d0)**2)
EquationOfTime = EqOfTimeCoef(1) + &
EqOfTimeCoef(2)*SineX + &
EqOfTimeCoef(3)*CosX + &
EqOfTimeCoef(4)*(SineX*CosX*2.d0) + &
EqOfTimeCoef(5)*(CosX**2 - SineX**2) + &
EqOfTimeCoef(6)*(SineX*(CosX**2 - SineX**2) + CosX*(SineX*CosX*2.d0)) + &
EqOfTimeCoef(7)*(CosX*(CosX**2 - SineX**2) - SineX*(SineX*CosX*2.d0)) + &
EqOfTimeCoef(8)*(2.d0*(SineX*CosX*2.d0)*(CosX**2 - SineX**2)) + &
EqOfTimeCoef(9)*((CosX**2 - SineX**2)**2 - (SineX*CosX*2.d0)**2)
RETURN
END SUBROUTINE SUN3