1 | pure function flux_mars77(R,decl,latitude,HA,albedo,fracir,fracscat) |
---|
2 | !*********************************************************************** |
---|
3 | ! flux_mars77: calculates insolation (incoming solar radiation) on Mars |
---|
4 | ! flat surface only; also works in polar regions |
---|
5 | ! |
---|
6 | ! R: distance from sun [AU] |
---|
7 | ! decl: planetocentric solar declination [radians] |
---|
8 | ! latitude: [radians] |
---|
9 | ! HA: hour angle [radians from noon, clockwise] |
---|
10 | ! fracir: fraction of absorption |
---|
11 | ! fracscat: fraction of scattering |
---|
12 | !*********************************************************************** |
---|
13 | implicit none |
---|
14 | real(8) flux_mars77 |
---|
15 | real(8), intent(IN) :: R,decl,latitude,HA,albedo,fracIR,fracScat |
---|
16 | real(8), parameter :: So=1365. ! [W/m^2] |
---|
17 | real(8), parameter :: sigSB=5.6704d-8 |
---|
18 | real(8) c1,s1,Qo,solarAttenuation,Q |
---|
19 | real(8) sinbeta,sinbetaNoon,Qdir,Qscat,Qlw,Fout |
---|
20 | |
---|
21 | c1 = cos(latitude)*cos(decl) |
---|
22 | s1 = sin(latitude)*sin(decl) |
---|
23 | ! beta = 90 minus incidence angle for horizontal surface |
---|
24 | ! beta = elevation of sun above (horizontal) horizon |
---|
25 | sinbeta = c1*cos(HA) + s1 |
---|
26 | sinbetaNoon = c1 + s1 |
---|
27 | sinbetaNoon = max(sinbetaNoon,0.d0) ! horizon |
---|
28 | |
---|
29 | Qo = So/(R**2) ! solar constant at Mars |
---|
30 | |
---|
31 | ! short-wavelength irradiance |
---|
32 | if (sinbeta>0.d0) then |
---|
33 | solarAttenuation = (1.- fracIR - fracScat)**(1./max(sinbeta,0.04)) |
---|
34 | Qdir = Qo*sinbeta*solarAttenuation |
---|
35 | Qscat = 0.5*Qo*fracScat |
---|
36 | Q = (1.-albedo)*(Qdir + Qscat) |
---|
37 | else |
---|
38 | Q = 0. |
---|
39 | endif |
---|
40 | |
---|
41 | ! atmospheric IR contribution based on Kieffer et al. (1977), JGR 82, 4249 |
---|
42 | Fout = 1.*sigSB*150**4 ! matters only in polar region |
---|
43 | Qlw = fracIR*max(Qo*sinbetaNoon,Fout) |
---|
44 | |
---|
45 | ! net flux = short-wavelength + long-wavelength irradiance |
---|
46 | flux_mars77 = Q + Qlw |
---|
47 | end function flux_mars77 |
---|
48 | |
---|
49 | |
---|
50 | |
---|
51 | pure subroutine flux_mars2(R,decl,latitude,HA,fracIR,fracScat, & |
---|
52 | & SlopeAngle,azFac,emax,Qdir,Qscat,Qlw) |
---|
53 | !***************************************************************************** |
---|
54 | ! flux_mars2: Insolation (incoming solar radiation) at Mars on sloped surface; |
---|
55 | ! returns several irradiances |
---|
56 | ! |
---|
57 | ! INPUTS: |
---|
58 | ! R: distance from sun [AU] |
---|
59 | ! decl: planetocentric solar declination [radians] |
---|
60 | ! latitude: [radians] |
---|
61 | ! HA: hour angle (radians from noon, clockwise) |
---|
62 | ! fracIR: fraction of absorption |
---|
63 | ! fracScat: fraction of scattering |
---|
64 | ! SlopeAngle: >0, [radians] |
---|
65 | ! azFac: azimuth of topographic gradient (radians east of north) |
---|
66 | ! azFac=0 is south-facing |
---|
67 | ! emax: maximum horizon elevation in direction of azimuth [radians] |
---|
68 | ! OUTPUTS: |
---|
69 | ! Qdir: direct incoming short-wavelength irradiance [W/m^2] |
---|
70 | ! Qscat: diffuse short-wavelength irradiance from atmosphere [W/m^2] |
---|
71 | ! Qlw: diffuse long-wavelength irradiance from atmosphere [W/m^2] |
---|
72 | !***************************************************************************** |
---|
73 | implicit none |
---|
74 | real(8), parameter :: pi=3.1415926535897932, So=1365. |
---|
75 | real(8), parameter :: sigSB=5.6704d-8 |
---|
76 | real(8), intent(IN) :: R,decl,latitude,HA,SlopeAngle,azFac,emax |
---|
77 | real(8), intent(IN) :: fracIR,fracScat |
---|
78 | real(8), intent(OUT) :: Qdir,Qscat,Qlw |
---|
79 | real(8) c1,s1,solarAttenuation,Qo |
---|
80 | real(8) sinbeta,sinbetaNoon,cosbeta,sintheta,azSun,buf,Fout |
---|
81 | |
---|
82 | c1 = cos(latitude)*cos(decl) |
---|
83 | s1 = sin(latitude)*sin(decl) |
---|
84 | ! beta = 90 minus incidence angle for horizontal surface |
---|
85 | ! beta = elevation of sun above (horizontal) horizon |
---|
86 | sinbeta = c1*cos(HA) + s1 |
---|
87 | sinbetaNoon = c1 + s1 |
---|
88 | sinbetaNoon = max(sinbetaNoon,0.d0) ! horizon |
---|
89 | |
---|
90 | cosbeta = sqrt(1-sinbeta**2) |
---|
91 | buf = (sin(decl)-sin(latitude)*sinbeta)/(cos(latitude)*cosbeta) |
---|
92 | if (buf>+1.) buf=+1.d0 ! roundoff |
---|
93 | if (buf<-1.) buf=-1.d0 ! roundoff |
---|
94 | azSun = acos(buf) |
---|
95 | if (sin(HA)>=0) azSun = 2*pi-azSun |
---|
96 | |
---|
97 | ! theta = 90 minus incidence angle for sloped surface |
---|
98 | sintheta = cos(SlopeAngle)*sinbeta - & |
---|
99 | & sin(SlopeAngle)*cosbeta*cos(azSun-azFac) |
---|
100 | if (cosbeta==0) sintheta=cos(SlopeAngle)*sinbeta ! zenith, where azSun=NaN |
---|
101 | |
---|
102 | if (sintheta<0.) sintheta=0. ! local horizon (self-shadowing) |
---|
103 | if (sinbeta<0.) sintheta=0. ! horizontal horizon at infinity |
---|
104 | if (sinbeta<sin(emax)) sintheta=0. ! distant horizon |
---|
105 | |
---|
106 | ! fluxes and contributions from atmosphere |
---|
107 | Qo = So/R**2 ! solar constant at Mars |
---|
108 | solarAttenuation = (1.- fracIR - fracScat)**(1./max(sinbeta,0.04d0)) |
---|
109 | Qdir = Qo*sintheta*solarAttenuation |
---|
110 | Fout = 1.*sigSB*150**4 ! matters only in polar region |
---|
111 | Qlw = fracIR*max(Qo*sinbetaNoon,Fout) |
---|
112 | if (sinbeta>0.d0) then |
---|
113 | Qscat = 0.5*fracScat*Qo |
---|
114 | else |
---|
115 | Qscat = 0. |
---|
116 | endif |
---|
117 | |
---|
118 | ! For a horizontal and unobstructed surface |
---|
119 | ! absorbed flux = (1-albedo)*(Qdir+Qscat) + emiss*Qlw |
---|
120 | ! |
---|
121 | ! For a tilted surface |
---|
122 | ! absorbed flux = (1-albedo)*(Qdir+Qscat*viewfactor) + emiss*Qlw*viewfactor |
---|
123 | ! then add irradiance from land in field of view |
---|
124 | ! in the case of a planar slope, viewfactor = cos(SlopeAngle/2.)**2 |
---|
125 | end subroutine flux_mars2 |
---|