Isis 3 Programmer Reference
HapkeAtm2.cpp
1 
6 /* SPDX-License-Identifier: CC0-1.0 */
7 #include <cmath>
8 #include "AtmosModel.h"
9 #include "Constants.h"
10 #include "HapkeAtm2.h"
11 #include "Pvl.h"
12 #include "PvlGroup.h"
13 #include "NumericalApproximation.h"
14 #include "IException.h"
15 #include "IString.h"
16 
17 using std::max;
18 
19 namespace Isis {
20  HapkeAtm2::HapkeAtm2(Pvl &pvl, PhotoModel &pmodel) : AtmosModel(pvl, pmodel) {
21  }
62  void HapkeAtm2::AtmosModelAlgorithm(double phase, double incidence,
63  double p_emission) {
64  double xx;
65  double maxval;
66  double munot, mu;
67  double p_emunot, emu;
68  double munotp, mup;
69  double f1munot, f1mmunot;
70  double xmunot, ymunot;
71  double xmu, ymu;
72  double gmunot, gmu;
73  double hpsq1;
74  double fix;
75  double f1mu, f1mmu;
76  double hahgt, hahgt0;
77  double phasefn;
78 
79  if(p_atmosTau == 0.0) {
80  p_pstd = 0.0;
81  p_trans = 1.0;
82  p_trans0 = 1.0;
83  p_sbar = 0.0;
84  p_transs = 1.0;
85  return;
86  }
87 
88  if(TauOrWhaChanged()) {
89 
90  // preparation includes exponential integrals p_e sub 2 through 4
91  p_wha2 = 0.5 * p_atmosWha;
92  p_e1 = AtmosModel::En(1, p_atmosTau);
93  p_e1_2 = AtmosModel::En(1, 2.0 * p_atmosTau);
94  p_e2 = AtmosModel::En(2, p_atmosTau);
95  p_e3 = AtmosModel::En(3, p_atmosTau);
96  p_e4 = AtmosModel::En(4, p_atmosTau);
97 
98  // chandra's gmn functions require fm and fn at mu=-1
99  xx = -p_atmosTau;
100  if(xx < -69.0) {
101  p_em = 0.0;
102  }
103  else if(xx > 69.0) {
104  p_em = 1.0e30;
105  }
106  else {
107  p_em = exp(xx);
108  }
109 
110  p_f1m = log(2.0) - p_em * p_e1 + p_e1_2;
111  p_f2m = -1.0 * (p_f1m + p_em * p_e2 - 1.0);
112  p_f3m = -1.0 * (p_f2m + p_em * p_e3 - 0.5);
113  p_g12 = (p_atmosTau * p_e1 * p_e2 + p_f1m + p_f2m) * 0.5;
114  p_g13 = (p_atmosTau * p_e1 * p_e3 + p_f1m + p_f3m) * (1.0 / 3.0);
115 
116  // chandra's g'mn functions require g'11 and f at mu=+1
117  xx = p_atmosTau;
118  if(xx < -69.0) {
119  p_e = 0.0;
120  }
121  else if(xx > 69.0) {
122  p_e = 1.0e30;
123  }
124  else {
125  p_e = exp(xx);
126  }
127 
128  p_f1 = Eulgam() + log(p_atmosTau) + p_e * p_e1;
129  p_f2 = p_f1 + p_e * p_e2 - 1.0;
130  p_f3 = p_f2 + p_e * p_e3 - 0.5;
131  p_g11p = AtmosModel::G11Prime(p_atmosTau);
132  p_g12p = (p_atmosTau * (p_e1 - p_g11p) + p_em * (p_f1 + p_f2)) * 0.25;
133  p_g13p = (p_atmosTau * (0.5 * p_e1 - p_g12p) + p_em * (p_f1 + p_f3)) * 0.2;
134 
135  // zeroth moments of (uncorrected) x and y times characteristic fn
136  p_x0 = p_wha2 * (1.0 + p_wha2 * p_g12);
137  p_y0 = p_wha2 * (p_e2 + p_wha2 * p_g12p);
138 
139  // higher-order correction term for x and y
140  p_delta = (1.0 - (p_x0 + p_y0) - (1.0 - p_atmosWha) / (1.0 - (p_x0 - p_y0))) / (p_atmosWha * (0.5 - p_e3));
141 
142  // moments of (corrected) x and y
143  p_alpha0 = 1.0 + p_wha2 * p_g12 + p_delta * (0.5 - p_e3);
144  p_alpha1 = 0.5 + p_wha2 * p_g13 + p_delta * ((1.0 / 3.0) - p_e4);
145  p_beta0 = p_e2 + p_wha2 * p_g12p + p_delta * (0.5 - p_e3);
146  p_beta1 = p_e3 + p_wha2 * p_g13p + p_delta * ((1.0 / 3.0) - p_e4);
147 
148  // prepare to find correct mixture of x and y in conservative case
149  if(p_atmosWha == 1.0) {
150  p_e5 = AtmosModel::En(5, p_atmosTau);
151  p_f4m = -1.0 * (p_f3m + p_em * p_e4 - (1.0 / 3.0));
152  p_g14 = (p_atmosTau * p_e1 * p_e4 + p_f1m + p_f4m) * 0.25;
153  p_f4 = p_f3 + p_e * p_e4 - (1.0 / 3.0);
154  p_g14p = (p_atmosTau * (0.5 * p_e1 - p_g13p) + p_em * (p_f1 + p_f4)) * (1.0 / 6.0);
155  p_alpha2 = (1.0 / 3.0) + p_wha2 * p_g14 + p_delta * (0.25 - p_e5);
156  p_beta2 = p_e4 + p_wha2 * p_g14p + p_delta * (0.25 - p_e5);
157  p_fixcon = (p_beta0 * p_atmosTau - p_alpha1 + p_beta1) /
158  ((p_alpha1 + p_beta1) * p_atmosTau + 2.0 * (p_alpha2 + p_beta2));
159  }
160 
161  // gamma will be a weighted sum of x and y functions
162  p_gammax = p_wha2 * p_beta0;
163  p_gammay = 1.0 - p_wha2 * p_alpha0;
164 
165  // sbar is total diffuse illumination
166  // isotropic part comes from moments, correction is numerical integral
167  if (p_atmosEstTau) {
169  } else {
171  }
172  p_sbar = 1.0 - ((2.0 - p_atmosWha * p_alpha0) * p_alpha1 + p_atmosWha * p_beta0 * p_beta1) + p_atmosHahgsb;
173 
174  SetOldTau(p_atmosTau);
175  SetOldWha(p_atmosWha);
176  }
177 
178  // correct the path lengths for planetary curvature
179  hpsq1 = pow((1.0 + p_atmosHnorm), 2.0) - 1.0;
180  munot = cos((PI / 180.0) * incidence);
181  maxval = max(1.0e-30, hpsq1 + munot * munot);
182  munotp = p_atmosHnorm / (sqrt(maxval) - munot);
183  munotp = max(munotp, p_atmosTau / 69.0);
184  mu = cos((PI / 180.0) * p_emission);
185  maxval = max(1.0e-30, hpsq1 + mu * mu);
186  mup = p_atmosHnorm / (sqrt(maxval) - mu);
187  mup = max(mup, p_atmosTau / 69.0);
188 
189  // build the x and y functions of mu0 and mu
190  maxval = max(1.0e-30, munotp);
191  xx = -p_atmosTau / maxval;
192 
193  if(xx < -69.0) {
194  p_emunot = 0.0;
195  }
196  else if(xx > 69.0) {
197  p_emunot = 1.0e30;
198  }
199  else {
200  p_emunot = exp(-p_atmosTau / munotp);
201  }
202 
203  maxval = max(1.0e-30, mup);
204  xx = -p_atmosTau / maxval;
205  if(xx < -69.0) {
206  emu = 0.0;
207  }
208  else if(xx > 69.0) {
209  emu = 1.0e30;
210  }
211  else {
212  emu = exp(-p_atmosTau / mup);
213  }
214 
215  // in the second approximation the x and y include the p_f1 function
216  xx = munotp;
217  if(fabs(xx - 1.0) < 1.0e-10) {
218  f1munot = p_f1;
219  f1mmunot = xx * (log(1.0 + 1.0 / xx) - p_e1 * p_emunot + AtmosModel::En(1, p_atmosTau * (1.0 + 1.0 / xx)));
220  }
221  else if(xx > 0.0) {
222  f1munot = xx * (log(xx / (1.0 - xx)) + p_e1 / p_emunot + AtmosModel::Ei(p_atmosTau * (1.0 / xx - 1.0)));
223  f1mmunot = xx * (log(1.0 + 1.0 / xx) - p_e1 * p_emunot + AtmosModel::En(1, p_atmosTau * (1.0 + 1.0 / xx)));
224  }
225  else {
226  std::string msg = "Negative length of planetary curvature ";
227  msg += "encountered";
228  throw IException(IException::Unknown, msg, _FILEINFO_);
229  }
230 
231  xx = mup;
232  if(fabs(xx - 1.0) < 1.0e-10) {
233  f1mu = p_f1;
234  f1mmu = xx * (log(1.0 + 1.0 / xx) - p_e1 * emu + AtmosModel::En(1, p_atmosTau * (1.0 + 1.0 / xx)));
235  }
236  else if(xx > 0.0) {
237  f1mu = xx * (log(xx / (1.0 - xx)) + p_e1 / emu + AtmosModel::Ei(p_atmosTau * (1.0 / xx - 1.0)));
238  f1mmu = xx * (log(1.0 + 1.0 / xx) - p_e1 * emu + AtmosModel::En(1, p_atmosTau * (1.0 + 1.0 / xx)));
239  }
240  else {
241  std::string msg = "Negative length of planetary curvature ";
242  msg += "encountered";
243  throw IException(IException::Unknown, msg, _FILEINFO_);
244  }
245 
246  xmunot = 1.0 + p_wha2 * f1mmunot + p_delta * munotp * (1.0 - p_emunot);
247  ymunot = p_emunot * (1.0 + p_wha2 * f1munot) + p_delta * munotp * (1.0 - p_emunot);
248  xmu = 1.0 + p_wha2 * f1mmu + p_delta * mup * (1.0 - emu);
249  ymu = emu * (1.0 + p_wha2 * f1mu) + p_delta * mup * (1.0 - emu);
250 
251  // mix the x and y as required in the conservative case
252  if(p_atmosWha == 1.0) {
253  fix = p_fixcon * munotp * (xmunot + ymunot);
254  xmunot = xmunot + fix;
255  ymunot = ymunot + fix;
256  fix = p_fixcon * mup * (xmu + ymu);
257  xmu = xmu + fix;
258  ymu = ymu + fix;
259  }
260 
261  // gamma1 functions come from x and y, with a correction for
262  // highly forward-scattered light as tabulated in hahgtTable
263  if (p_atmosEstTau) {
266  NumericalAtmosApprox qromb;
267  p_atmosAtmSwitch = 1;
268  qromb.Reset();
269  p_atmosInc = incidence;
270  p_atmosMunot = cos((PI / 180.0) * incidence);
271  p_atmosSini = sin((PI / 180.0) * incidence);
272  hahgt = qromb.RombergsMethod(this, sub, 0, 180);
273  gmunot = p_gammax * xmunot + p_gammay * ymunot + hahgt * AtmosWha() / 360.0;
274  p_atmosInc = p_emission;
275  p_atmosMunot = cos((PI / 180.0) * p_emission);
276  p_atmosSini = sin((PI / 180.0) * p_emission);
277  hahgt = qromb.RombergsMethod(this, sub, 0, 180);
278  gmu = p_gammax * xmu + p_gammay * ymu + hahgt * AtmosWha() / 360.0;
279  } else {
281  gmunot = p_gammax * xmunot + p_gammay * ymunot + hahgt;
283  gmu = p_gammax * xmu + p_gammay * ymu + hahgt;
284  }
285 
286  // purely atmos term uses x and y (plus single-particle phase
287  // function correction)
288  phasefn = (1.0 - p_atmosHga * p_atmosHga) / pow(1.0 + 2.0 * p_atmosHga *
289  cos((PI / 180.0) * phase) + p_atmosHga * p_atmosHga, 1.5);
290  p_pstd = 0.25 * p_atmosWha * munotp / (munotp + mup) * ((xmunot * xmu - ymunot * ymu) +
291  (phasefn - 1.0) * (1.0 - emu * p_emunot));
292 
293  // xmitted surface term uses gammas
294  p_trans = gmunot * gmu;
295 
296  // finally, never-scattered term is given by pure attenuation, with
297  // a correction for highly forward-scattered light (on the way down
298  // but not on the way up) as tabulated in hahgt0Table
299  if (p_atmosEstTau) {
302  NumericalAtmosApprox qromb;
303  p_atmosAtmSwitch = 3;
304  qromb.Reset();
305  p_atmosInc = incidence;
306  p_atmosMunot = cos((PI / 180.0) * incidence);
307  p_atmosSini = sin((PI / 180.0) * incidence);
308  hahgt0 = qromb.RombergsMethod(this, sub, 0, 180);
309  hahgt0 = hahgt0 * AtmosWha() * p_atmosMunot / (360.0 * p_atmosSini);
310  } else {
312  }
313  p_trans0 = (p_emunot + hahgt0) * emu;
314 
315  // Calculate the transmission of light that must be subtracted from a shadow. This
316  // includes direct flux and the scattered flux in the upsun half of the sky
317  // downwelling onto the surface, and the usual transmission upward.
318  if (p_atmosEstTau) {
321  NumericalAtmosApprox qromb;
322  p_atmosAtmSwitch = 1;
323  qromb.Reset();
324  hahgt = qromb.RombergsMethod(this, sub, 90, 180);
325  hahgt = .5 * (p_gammax * xmunot + p_gammay * ymunot - p_emunot) + hahgt *
326  AtmosWha() / 360.0;
327  } else {
329  }
330  p_transs = (p_emunot + hahgt) * emu;
331 
332  }
333 }
334 
335 extern "C" Isis::AtmosModel *HapkeAtm2Plugin(Isis::Pvl &pvl, Isis::PhotoModel &pmodel) {
336  return new Isis::HapkeAtm2(pvl, pmodel);
337 }
Isis::NumericalAtmosApprox::IntegFunc
IntegFunc
This enum defines function to be integrated by Romberg's method.
Definition: NumericalAtmosApprox.h:43
Isis::NumericalApproximation::Extrapolate
@ Extrapolate
Evaluate() attempts to extrapolate if a is outside of the domain. This is only valid for NumericalApp...
Definition: NumericalApproximation.h:814
Isis::AtmosModel::AtmosWha
double AtmosWha() const
Return atmospheric Wha value.
Definition: AtmosModel.h:123
Isis::AtmosModel::TauOrWhaChanged
bool TauOrWhaChanged() const
Checks whether tau or wha have changed.
Definition: AtmosModel.cpp:954
Isis::PhotoModel
Definition: PhotoModel.h:41
Isis::PI
const double PI
The mathematical constant PI.
Definition: Constants.h:40
Isis::AtmosModel::p_pstd
double p_pstd
Pure atmospheric-scattering term.
Definition: AtmosModel.h:258
Isis::AtmosModel::En
static double En(unsigned int n, double x)
This routine evaluates the generalized exponential integral, En(x).
Definition: AtmosModel.cpp:370
Isis::IException::Unknown
@ Unknown
A type of error that cannot be classified as any of the other error types.
Definition: IException.h:118
Isis::NumericalAtmosApprox
This class extends Isis::NumericalApproximation.
Definition: NumericalAtmosApprox.h:32
Isis::AtmosModel
Isotropic atmos scattering model.
Definition: AtmosModel.h:60
Isis::Pvl
Container for cube-like labels.
Definition: Pvl.h:119
Isis::HapkeAtm2
Definition: HapkeAtm2.h:40
Isis::AtmosModel::p_trans
double p_trans
Transmission of surface reflected light through the atmosphere overall.
Definition: AtmosModel.h:259
Isis::AtmosModel::p_atmosEstTau
bool p_atmosEstTau
Estimate optical depth tau using shadows.
Definition: AtmosModel.h:269
Isis::AtmosModel::GenerateHahgTables
void GenerateHahgTables()
This method computes the values of the atmospheric Hahg and Hahg0 tables and sets the properties of t...
Definition: AtmosModel.cpp:637
Isis::AtmosModel::p_transs
double p_transs
Transmission of light that must be subtracted from the flat surface model to get the shadow model.
Definition: AtmosModel.h:261
Isis::AtmosModel::p_atmosHahgtSpline
NumericalApproximation p_atmosHahgtSpline
Spline object for the atmospheric Hahg Table. Properties are set in GenerateHahgTables().
Definition: AtmosModel.h:285
Isis::IException
Isis exception class.
Definition: IException.h:91
Isis::AtmosModel::p_atmosHnorm
double p_atmosHnorm
Atmospheric shell thickness normalized to planet radius.
Definition: AtmosModel.h:267
Isis::AtmosModel::p_atmosHahgt0Spline
NumericalApproximation p_atmosHahgt0Spline
Spline object for the atmospheric Hahg0 Table. Properties are set in GenerateHahgTables().
Definition: AtmosModel.h:287
Isis::AtmosModel::GenerateHahgTablesShadow
void GenerateHahgTablesShadow()
This method is a modified version of the GenerateHahgTables method and is used solely for shadow mode...
Definition: AtmosModel.cpp:726
Isis::AtmosModel::Ei
static double Ei(double x)
This routine computes the exponential integral, Ei(x).
Definition: AtmosModel.cpp:229
Isis::NumericalApproximation::Evaluate
double Evaluate(const double a, const ExtrapType &etype=ThrowError)
Calculates interpolated or extrapolated value of tabulated data set for given domain value.
Definition: NumericalApproximation.cpp:836
Isis::AtmosModel::G11Prime
static double G11Prime(double tau)
Perform Chandra and Van de Hulst's series approximation for the g'11 function needed in second order ...
Definition: AtmosModel.cpp:153
Isis::AtmosModel::p_sbar
double p_sbar
Illumination of the ground by the sky.
Definition: AtmosModel.h:262
Isis::HapkeAtm2::AtmosModelAlgorithm
virtual void AtmosModelAlgorithm(double phase, double incidence, double emission)
Henyey-Greenstein atmos scattering in the 1st approximation.
Definition: HapkeAtm2.cpp:62
Isis::AtmosModel::p_trans0
double p_trans0
Transmission of surface reflected light through the atmosphere with no scatterings in the atmosphere.
Definition: AtmosModel.h:260
Isis::NumericalAtmosApprox::RombergsMethod
double RombergsMethod(AtmosModel *am, IntegFunc sub, double a, double b)
This variation on the NumericalApproximation method integrates a specified AtmosModel function rather...
Definition: NumericalAtmosApprox.cpp:52
Isis::NumericalApproximation::Reset
void Reset()
Resets the state of the object.
Definition: NumericalApproximation.cpp:2251
Isis::NumericalAtmosApprox::OuterFunction
@ OuterFunction
Indicates that Romberg's method will integrate the function OutrFunc2Bint()
Definition: NumericalAtmosApprox.h:43
Isis
This is free and unencumbered software released into the public domain.
Definition: Apollo.h:16