libTheSky
Routines to compute sky positions of Sun, Moon, planets and more
All Namespaces Files Functions Variables Pages
daylight.f90
Go to the documentation of this file.
1!> \file daylight.f90 Procedures that deal with daylight for libTheSky
2
3
4! Copyright (c) 2002-2025 Marc van der Sluys - Nikhef/Utrecht University - marc.vandersluys.nl
5!
6! This file is part of the libTheSky package,
7! see: https://libthesky.sf.net/
8!
9! This is free software: you can redistribute it and/or modify it under the terms of the
10! European Union Public Licence 1.2 (EUPL 1.2).
11!
12! This software is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY;
13! without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
14! See the EU Public Licence for more details.
15!
16! You should have received a copy of the European Union Public Licence along with this code.
17! If not, see <https://www.eupl.eu/1.2/en/>.
18
19
20! extinction_sun_airmass: Compute an approximation for the bolometric atmospheric extinction for the Sun with a given AM
21! extinction_sun: Compute an approximation for the bolometric atmospheric extinction for the Sun with a given alt
22! solar_radiation: Compute the normal and horizontal beam (direct) solar radiation for a given altitude of the Sun
23! diffuse_radiation_Perez87: Compute diffuse radiation on an inclined surface using the Perez 1987 model
24
25
26!***********************************************************************************************************************************
27!> \brief Daylight procedures
28
30 implicit none
31 save
32
33contains
34
35
36 !*********************************************************************************************************************************
37 !> \brief Compute an approximation for the bolometric atmospheric extinction factor for the Sun with a given air mass
38 !!
39 !! \param airmass Airmass for the position of the Sun
40 !! \retval extinction_sun_airmass The approximated bolometric atmospheric extinction factor for the Sun
41 !!
42 !! \note - extinction_fac = 1: no extinction, extinction_fac > 1 extinction.
43 !! - Hence, the flux, corrected for extinction, should be f' = f / extinction_fac(alt,ele)
44 !! - Fit of the power extinction computed by the NREL SMARTS code (valid for airmass <= 38.2):
45 !! - Gueymard, C, Professional Paper FSEC-PF-270-95, 1995
46 !! - Gueymard, C, Solar Energy, Vol. 71, No. 5, pp. 325-346, 2001
47
48 function extinction_sun_airmass(airmass)
49 use sufr_kinds, only: double
50
51 implicit none
52 real(double), intent(in) :: airmass
53 integer, parameter :: ncoef = 11
54 integer :: icoef
55 real(double) :: extinction_sun_airmass, coefs(ncoef), ampow
56
57 if(airmass.gt.38.2d0) then
58
59 extinction_sun_airmass = sqrt(huge(extinction_sun_airmass)) + airmass ! Very bad, getting worse for higher AM for solvers
60
61 else
62
63 coefs = [ 9.1619283d-2, 2.6098406d-1,-3.6487512d-2, 6.4036283d-3,-8.1993861d-4, 6.9994043d-5,-3.8980993d-6, 1.3929599d-7, &
64 -3.0685834d-9, 3.7844273d-11,-1.9955057d-13]
65
66 ampow = 1.d0 ! AM^0
67 extinction_sun_airmass = coefs(1) ! c_1 * AM^0
68 do icoef=2,ncoef
69 ampow = ampow * airmass ! AM^(i-1)
70 extinction_sun_airmass = extinction_sun_airmass + coefs(icoef) * ampow ! + c_i * AM^(i-1)
71 end do
72
74
75 end if
76
77 end function extinction_sun_airmass
78 !*********************************************************************************************************************************
79
80
81
82 !*********************************************************************************************************************************
83 !> \brief Compute an approximation for the bolometric atmospheric extinction factor for the Sun with a given altitude
84 !!
85 !! \param alt TRUE altitude of the Sun (radians)
86 !! \retval extinction_sun The approximated bolometric atmospheric extinction factor for the Sun
87 !!
88 !! \note - extinction_fac = 1: no extinction, extinction_fac > 1 extinction.
89 !! - Hence, the flux, corrected for extinction, should be f' = f / extinction_fac(alt,ele)
90
91 function extinction_sun(alt)
92 use sufr_kinds, only: double
93 use thesky_visibility, only: airmass
94
95 implicit none
96 real(double), intent(in) :: alt
97 real(double) :: extinction_sun
98
100
101 end function extinction_sun
102 !*********************************************************************************************************************************
103
104
105
106 !*********************************************************************************************************************************
107 !> \brief Compute the normal and horizontal beam (direct) solar radiation for a given altitude of the Sun,
108 !! assuming a cloudless sky (and sea level)
109 !!
110 !! \param alt TRUE altitude of the Sun (radians)
111 !!
112 !! \param beam_norm Normal beam radiation, perpendicular to the position vector of the Sun (W/m2) (output)
113 !! \param beam_horiz Beam radiation on a horizontal surface (W/m2) (output)
114 !!
115 !! \see function extinction_sun()
116
117 subroutine solar_radiation(alt, beam_norm, beam_horiz)
118 use sufr_kinds, only: double
119 use sufr_constants, only: solconst
120
121 implicit none
122 real(double), intent(in) :: alt
123 real(double), intent(out) :: beam_norm
124 real(double), intent(out), optional :: beam_horiz
125
126
127 beam_norm = solconst / extinction_sun(alt) ! Normal radiation
128 if(present(beam_horiz)) beam_horiz = beam_norm * sin(alt) ! Radiation on a horizontal surface
129
130 end subroutine solar_radiation
131 !*********************************************************************************************************************************
132
133
134 !*********************************************************************************************************************************
135 !> \brief A simplified clear-sky model for direct and diffuse insolation on horizontal surfaces (a.k.a. as the Bird model)
136 !!
137 !! \param alt Sun altitude above the horizon (rad)
138 !!
139 !! \param Io Solar 'constant' (W/m^2 - optional, default: 1361.5)
140 !! \param Rsun Sun distance (AU - optional, default: 1)
141 !! \param Press Air pressure at the observer's site, corrected for altitude (hPa - optional, default: 1013)
142 !!
143 !! \param Uo Ozone abundance in a vertical column (cm - optional, default: 0.34)
144 !! \param Uw Percipitable water-vapor abundance in a vertical column (cm - optional, default: 1.42)
145 !!
146 !! \param Ta5 Aerosol optical depth from surface in vertical path at 500 nm (optional, default: 0.2661)
147 !! \param Ta3 Aerosol optical depth from surface in vertical path at 380 nm (optional, default: 0.3538)
148 !! \param Ba Aerosol forward-scattering ratio (optional, 0.82-0.86, default: 0.84)
149 !! \param K1 Aerosol-absorptance constant (optional, rural: 0.0933, urban: 0.385, default: 0.1)
150 !!
151 !! \param Rg Ground albedo (optional, fraction - default: 0.2)
152 !!
153 !!
154 !! \param Itot Total insolation on a horizontal surface (W/m^2 - optional) (output)
155 !! \param Idir Direct (beam) insolation on a horizontal surface (W/m^2 - optional) (output)
156 !! \param Idif Diffuse insolation on a horizontal surface (W/m^2 - optional) (output)
157 !! \param Igr Ground-reflection insolation from a horizontal surface (W/m^2 - optional) (output)
158 !!
159 !!
160 !! \see Bird & Hulstrom, A simplified clear-sky model for direct and diffuse insolation on horizontal surfaces, SERI/TR-642-761 (1981)
161 !!
162 !! \note The value of Taa does not agree with tabulated values from the paper, and hence neither do dependent values (except for AM~1).
163 !! When I substitute their values for Taa, everything matches perfectly. Error in their formula, or (hopefully!) in their table?
164
165 subroutine clearsky_bird(alt, Io,Rsun,Press, Uo,Uw, Ta5,Ta3,Ba,K1, Rg, Itot,Idir,Idif,Igr)
166 use sufr_kinds, only: double
167 use sufr_constants, only: pio2, r2d !, solConst
168
169 implicit none
170 real(double), intent(in) :: alt
171 real(double), intent(in), optional :: Io,Rsun,Press, Uo,Uw, Ta5,Ta3,Ba,K1, Rg
172 real(double), intent(out), optional :: Itot, Idir, Idif, Igr
173
174 real(double) :: Z,cosZ, AM,AMp, Tr, Xo,To, Tum, Xw,Tw, Tau,Ta,Taa,Tas, Rs, tmpVar
175 real(double) :: RsunL,IoL,PressL, UoL,UwL, Ta5L,Ta3L,BaL,K1L, RgL, ItotL,IdirL,IdifL
176
177 ! Assign optional variables to local variables:
178 rsunl = 1.d0 ! Default Sun distance: 1 AU
179 if(present(rsun)) rsunl = rsun
180 iol = 1353.d0 ! solConst ! Default solar "constant": 1353 (1361.5) W/m^2
181 if(present(io)) iol = io
182 pressl = 1013.d0 ! Default air pressure: 1013 hPa
183 if(present(press)) pressl = press
184
185 uol = 0.34d0 ! Default ozone abundance: 0.34
186 if(present(uo)) uol = uo
187 uwl = 1.42d0 ! Default water-vapor abundance: 1.42
188 if(present(uw)) uwl = uw
189
190 ta5l = 0.2661d0 ! Default aerosol vertical optical depth at 500nm: 0.2661 cm
191 if(present(ta5)) ta5l = ta5
192 ta3l = 0.3538d0 ! Default aerosol vertical optical depth at 500nm: 0.3538 cm
193 if(present(ta3)) ta3l = ta3
194 bal = 0.84d0 ! Default aerosol forward-scattering ratio: 0.84
195 if(present(ba)) bal = ba
196 k1l = 0.1d0 ! Default aerosol-absorptance constant (rural: 0.0933, urban: 0.385, adviced: 0.1)
197 if(present(k1)) k1l = k1
198
199 rgl = 0.2d0 ! Default ground albedo: 0.2
200 if(present(rg)) rgl = rg
201
202
203
204 z = pio2 - alt ! Solar zenith angle
205 cosz = cos(z) ! Save a few CPU cycles
206
207
208 ! Relative air mass for the solar vector:
209 am = 1.d0/(cosz + 0.15d0 * (93.885-z*r2d)**(-1.25d0)) ! Air mass
210 amp = am * pressl / 1013.d0 ! Pressure-corrected air mass
211
212 ! TRANSMISSION EQUATIONS:
213 ! Rayleigh scattering:
214 tr = exp( -0.0903d0 * amp**0.84d0 * (1.d0 + amp - amp**1.01d0) )
215
216 ! Ozone:
217 xo = uol*am ! Amount of ozone in the direction of the Sun
218 to = 1.d0 - 0.1611d0 * xo * (1.d0+139.48d0*xo)**(-0.3035d0) - 0.002715 * xo / (1.d0 + 0.044d0*xo + 0.0003d0*xo**2) ! Transmittance of ozone absorptance
219
220 ! Uniformly mixed gases (CO2, O2):
221 tum = exp(-0.0127d0 * amp**0.26d0) ! Transmittance of mixed-gas absorptance
222
223 ! Water vapor:
224 xw = am*uwl ! Amount of water vapor in the direction of the Sun
225 tw = 1.d0 - 2.4959d0 * xw / ((1.d0 + 79.034d0*xw)**0.6828d0 + 6.385d0*xw) ! Transmittance of water-vapor absorptance - Tw = 1-Aw
226
227 ! Daily turbidity:
228 tau = 0.2758d0*ta3l + 0.35d0*ta5l ! Broadband turbidity: aerosol optical depth from surface in a vertical column
229 ta = exp( -tau**0.873d0 * (1.d0 + tau - tau**0.7088d0) * am**0.9108d0 ) ! Transmittance of aerosol absorptance and scattering
230 taa = 1.d0 - k1l * (1.d0 - am + am**1.06d0) * (1.d0-ta) ! Transmittance of aerosol absorptance - this does not agree with tabulated values from the paper (except for AM~1). When I substitute their values for Taa, everything matches perfectly. Error in their formula, or in their table?
231 tas = ta/taa ! Transmittance of aerosol scattering
232 rs = 0.0685d0 + (1.d0-bal) * (1.d0-tas) ! Sky albedo
233
234
235 ! IRRADIANCE EQUATIONS - Itot, Idir, Idif are always computed, Igr only if desired:
236
237 ! Direct radiation on a horizontal surface:
238 tmpvar = iol * cosz * to * tum * tw ! Save a few CPU cycles
239 idirl = 0.9662d0 * tmpvar * tr * ta / rsunl**2
240
241 ! Diffuse (scattered) radiation on a horizontal surface:
242 idifl = 0.79d0 * tmpvar * taa * (0.5d0*(1.d0-tr) + bal*(1.d0-tas)) / (1.d0 - am + am**1.02d0)
243
244 ! Total (direct+diffuse) radiation on a horizontal surface:
245 itotl = (idirl+idifl) / (1.d0 - rgl*rs)
246
247
248 ! Copy local variables to optional output variables:
249 if(present(itot)) itot = itotl
250 if(present(idir)) idir = idirl
251 if(present(idif)) idif = idifl
252 if(present(igr)) igr = itotl - (idirl+idifl) ! Ground-reflected radiation from a horizontal surface
253
254 end subroutine clearsky_bird
255 !*********************************************************************************************************************************
256
257
258
259
260
261 !*********************************************************************************************************************************
262 !> \brief Compute diffuse radiation on an inclined surface using the older (1987) Perez model
263 !!
264 !! \param DoY Day of year (Nday)
265 !! \param alt Altitude of the Sun (radians)
266 !!
267 !! \param surfIncl Surface inclination wrt horizontal (radians) - 0 = horizontal, pi/2 = vertical
268 !! \param theta Angle between surface normal vector and Sun position vector (radians)
269 !!
270 !! \param Gbeam_n Beam (direct) normal radiation (W/m2; in the direction of the Sun)
271 !! \param Gdif_hor Diffuse radiation on a horizontal surface (W/m2)
272 !!
273 !! \param Gdif_inc Diffuse irradiation on the inclined surface (W/m2) (output)
274 !!
275 !! \param Gdif_inc_is Diffuse irradiation on the inclined surface - isotropic part (optional; W/m2) (output)
276 !! \param Gdif_inc_cs Diffuse irradiation on the inclined surface - circumsolar part (optional; W/m2) (output)
277 !! \param Gdif_inc_hz Diffuse irradiation on the inclined surface - horizon-band part (optional; W/m2) (output)
278 !!
279 !! \see Perez et al. Solar Energy Vol. 39, Nr. 3, p. 221 (1987) - references to equations and tables are to this paper.
280 !! Most equations can be found in the Nomenclature section at the end of the paper (p.230). I use a and c here, not b and d.
281 !!
282 !! \todo Implement Perez et al. Solar Energy Vol. 44, Nr. 5, p. 271 (1990)
283
284 subroutine diffuse_radiation_perez87(DoY, alt, surfIncl, theta, Gbeam_n,Gdif_hor, Gdif_inc, Gdif_inc_is, Gdif_inc_cs, Gdif_inc_hz)
285 use sufr_kinds, only: double
286 use sufr_constants, only: pi2,pio2, d2r,r2d
287
288 implicit none
289 integer, intent(in) :: DoY
290 real(double), intent(in) :: alt, surfIncl, theta, Gbeam_n,Gdif_hor
291 real(double), intent(out) :: Gdif_inc
292 real(double), intent(out), optional :: Gdif_inc_is, Gdif_inc_cs, Gdif_inc_hz
293 integer :: f11,f12,f13, f21,f22,f23
294 real(double) :: zeta, AM0rad, Mair,Delta,epsilon, alpha, psiC,psiH, chiC,chiH, F(6),F1,F2, A,C
295 real(double) :: Gdif_inc_iso, Gdif_inc_csl, Gdif_inc_hzl
296
297
298 ! *** Compute the brightness coefficients for the isotropic (F1), circumsolar (F1) and horizon (F2) regions ***
299
300 ! 'External' (AM0) radiation:
301 am0rad = 1370.d0 * (1.d0 + 0.00333d0 * cos(pi2/365.d0 * doy))
302
303 ! Air mass:
304 if(alt .lt. -3.885d0*d2r) then
305 mair = 99.d0
306 else if(alt .lt. 10.d0*d2r) then
307 mair = 1.d0 / ( sin(alt) + 0.15d0 * (alt*r2d + 3.885d0)**(-1.253d0) )
308 else
309 mair = 1.d0 / sin(alt)
310 end if
311 delta = gdif_hor * mair / am0rad ! Brightness of overcast sky - par. 2.2.4 (a)
312
313
314 ! Cloud cover: epsilon; epsilon ~ 1: overcast, epsilon -> infinity: clear (epsilon ~ 1/fraction of covered sky)
315 ! Needed for correct row in Table 1
316 if(gdif_hor.le.0.d0) then ! Division by zero
317 if(gbeam_n.le.0.d0) then ! No direct light: 0/0
318 epsilon = 0.d0 ! -> completely overcast - first row of Table 1
319 else ! Some direct daylight: x/0 = large
320 epsilon = 99.d0 ! -> completely clear, should be >11 for last row of Table 1
321 end if
322 else
323 epsilon = (gdif_hor + gbeam_n) / gdif_hor ! Overcast: epsilon ~ 1, clear: epsilon -> infinity
324 end if
325
326
327 ! Table 1
328 f11=1; f12=2; f13=3; f21=4; f22=5; f23=6
329 if(epsilon .le. 1.056d0) then
330 f = [-0.011d0, 0.748d0, -0.080d0, -0.048d0, 0.073d0, -0.024d0]
331 else if(epsilon .le. 1.253d0) then
332 f = [-0.038d0, 1.115d0, -0.109d0, -0.023d0, 0.106d0, -0.037d0]
333 else if(epsilon .le. 1.586d0) then
334 f = [ 0.166d0, 0.909d0, -0.179d0, 0.062d0, -0.021d0, -0.050d0]
335 else if(epsilon .le. 2.134d0) then
336 f = [ 0.419d0, 0.646d0, -0.262d0, 0.140d0, -0.167d0, -0.042d0]
337 else if(epsilon .le. 3.230d0) then
338 f = [ 0.710d0, 0.025d0, -0.290d0, 0.243d0, -0.511d0, -0.004d0]
339 else if(epsilon .le. 5.980d0) then
340 f = [ 0.857d0, -0.370d0, -0.279d0, 0.267d0, -0.792d0, 0.076d0]
341 else if(epsilon .le. 10.080d0) then
342 f = [ 0.734d0, -0.073d0, -0.228d0, 0.231d0, -1.180d0, 0.199d0]
343 else
344 f = [ 0.421d0, -0.661d0, 0.097d0, 0.119d0, -2.125d0, 0.446d0]
345 end if
346
347 zeta = pio2 - alt ! Zenith angle = pi/2 - alt
348 f1 = f(f11) + f(f12) * delta + f(f13) * zeta ! Isotropic, circumsolar brightness coefficient
349 f2 = f(f21) + f(f22) * delta + f(f23) * zeta ! Horizon brightness coefficient
350
351
352
353
354 ! *** Compute the mean solid angles occupied by the circumsolar region (C and A, needed for Eq.8) ***
355
356 alpha = 25.d0*d2r ! Half angle of the circumsolar region (degrees -> radians; below Eq.9)
357
358
359 ! Solid angle of the circumsolar region weighted by incidence on the HORIZONTAL (variable C, subscript H;
360 ! see Nomenclature, under c):
361 ! psiH:
362 if(zeta .gt. pio2 - alpha) then
363 psih = 0.5d0 * (pio2 - zeta + alpha) / alpha ! Dimensionless ratio
364 else
365 psih = 1.d0
366 end if
367
368 ! chiH:
369 if(zeta .lt. pio2 - alpha) then
370 chih = cos(zeta) ! = sin(alt)
371 else
372 chih = psih * sin(psih*alpha)
373 end if
374
375 c = 2 * (1.d0 - cos(alpha)) * chih ! Solid angle of the circumsolar region, weighted by HORIZONTAL incidence
376
377
378 ! Solid angle of the circumsolar region weighted by incidence on the SLOPE (variable A, subscript C;
379 ! see Nomenclature, under c):
380 ! psiC:
381 psic = 0.5d0 * (pio2 - theta + alpha) / alpha
382
383 ! chiC:
384 if(theta .lt. pio2 - alpha) then
385 chic = psih * cos(theta)
386 else if(theta .lt. pio2 + alpha) then
387 chic = psih * psic * sin(psic*alpha)
388 else
389 chic = 0.d0
390 end if
391
392 a = 2 * (1.d0 - cos(alpha)) * chic ! Solid angle of the circumsolar region, weighted by SLOPE incidence
393
394
395
396 ! Diffuse radiation from circumsolar (F1) and horizon (F2) regions on the inclined surface (Eq.8):
397 gdif_inc_iso = gdif_hor * 0.5d0 * (1.d0 + cos(surfincl)) * (1.d0 - f1) ! Isotropic
398 gdif_inc_csl = gdif_hor * f1 * a/c ! Circumsolar
399 gdif_inc_hzl = gdif_hor * f2 * sin(surfincl) ! Horizon band
400
401 gdif_inc = max(gdif_inc_iso + gdif_inc_csl + gdif_inc_hzl, 0.d0) ! Note: components are sometimes negative
402
403 ! Assign optional return values:
404 if(present(gdif_inc_is)) gdif_inc_is = gdif_inc_iso
405 if(present(gdif_inc_cs)) gdif_inc_cs = gdif_inc_csl
406 if(present(gdif_inc_hz)) gdif_inc_hz = gdif_inc_hzl
407
408 end subroutine diffuse_radiation_perez87
409 !*********************************************************************************************************************************
410
411
412
413 !*********************************************************************************************************************************
414 !> \brief Compute the projection factor of direct solar radiation (DNI) on a (sloped) surface.
415 !!
416 !! This function returns the projection factor of direct sunlight on a surface with given orientation,
417 !! useful for e.g. insolation on solar panels, solar collectors or windows. The projection factor equals
418 !! the cosine of the angle between the normal vector of the surface and the position vector of the Sun.
419 !!
420 !! \param beta Inclination angle of the surface (w.r.t. the horizontal) (radians)
421 !! \param gamma Azimuth angle of the surface (0=south, pi/2=west, ±pi=north, -pi/2=east) (radians)
422 !! \param sunAz Azimuth of the Sun (0=south, pi/2=west, ±pi=north, -pi/2=east) (radians)
423 !! \param sunAlt Apparent altitude of the Sun (radians)
424 !!
425 !! \retval project_sunlight_on_surface The projection factor for direct solar radiation (DNI) on a (sloped) surface (0-1).
426 !!
427 !! \note
428 !! Note that different definitions for gamma and sunAz are possible, as long as they correspond.
429 !!
430 !! \see
431 !! Celestial mechanics in a nutshell, Sect. 4.3: Insolation on an inclined surface (https://CMiaNS.sf.net).
432
433 function project_sunlight_on_surface(beta,gamma, sunAz,sunAlt)
434 use sufr_kinds, only: double
435
436 implicit none
437 real(double), intent(in) :: beta,gamma, sunaz,sunalt
438 real(double) :: project_sunlight_on_surface
439
440 project_sunlight_on_surface = sin(sunalt)*cos(beta) + cos(sunalt)*sin(beta)*cos(sunaz - gamma)
441
442
443 end function project_sunlight_on_surface
444 !*********************************************************************************************************************************
445
446
447
448
449end module thesky_daylight
450!***********************************************************************************************************************************
Daylight procedures.
Definition daylight.f90:29
subroutine clearsky_bird(alt, io, rsun, press, uo, uw, ta5, ta3, ba, k1, rg, itot, idir, idif, igr)
A simplified clear-sky model for direct and diffuse insolation on horizontal surfaces (a....
Definition daylight.f90:166
real(double) function extinction_sun(alt)
Compute an approximation for the bolometric atmospheric extinction factor for the Sun with a given al...
Definition daylight.f90:92
real(double) function project_sunlight_on_surface(beta, gamma, sunaz, sunalt)
Compute the projection factor of direct solar radiation (DNI) on a (sloped) surface.
Definition daylight.f90:434
subroutine solar_radiation(alt, beam_norm, beam_horiz)
Compute the normal and horizontal beam (direct) solar radiation for a given altitude of the Sun,...
Definition daylight.f90:118
real(double) function extinction_sun_airmass(airmass)
Compute an approximation for the bolometric atmospheric extinction factor for the Sun with a given ai...
Definition daylight.f90:49
subroutine diffuse_radiation_perez87(doy, alt, surfincl, theta, gbeam_n, gdif_hor, gdif_inc, gdif_inc_is, gdif_inc_cs, gdif_inc_hz)
Compute diffuse radiation on an inclined surface using the older (1987) Perez model.
Definition daylight.f90:285
Procedures to determine the visibility of objects.
real(double) function airmass(alt)
Compute the airmass for a celestial object with a given TRUE altitude.