UPP  V11.0.0
 All Data Structures Files Functions Pages
GEO_ZENITH_ANGLE.f
1  SUBROUTINE geo_zenith_angle(i,j,RLAT,RLON,SLAT,SLON,ZA)
2 !
3 !************************************************************************
4 !* *
5 !* Module Name: GOES_ZA *
6 !* *
7 !* Language: Fortran-90 Library: *
8 !* Version.Rev: 1.0 16 JUL 87 Programmer: KLEESPIES *
9 !* 1.1 16 Mar 89 Kleespies *
10 !* Fix bug in ZA computation. *
11 !* Sep. 2010 Chuang: convert to Fortran 90 *
12 ! and incoporate to unified post *
13 !* Calling Seq: CALL GOES_ZA(RLAT,RLON,SLAT,SLON,ZA) *
14 !* Description: Computes local zenith angle from a point on the *
15 !* earth's surface to geosynchronous altitude. This uses *
16 !* spherical geometry, so it isn't fancy. A ZA gt 90 deg *
17 !* means the earth station is over the horizon from the *
18 !* satellite. *
19 !* Input Args: R*4 RLAT latitude of earth point +- 90 deg *
20 !* R*4 RLON longitude of earth point deg + E *
21 !* R*4 SLAT latitude of subsatellite point *
22 !* R*4 SLON longitude of subsatellite point *
23 !* *
24 !* Output Args: R*4 ZA zenith angle to geostationary *
25 !* altitude. *
26 !* *
27 !* Common Blks: none *
28 !* *
29 !* Include: none *
30 !* *
31 !* Externals: none *
32 !* *
33 !* Data Files: none *
34 !* *
35 !* Restrictions: Uses spherical geometry, so is not totally *
36 !* accurate. Makes no check for quadrant changes, so may *
37 !* have problems around the prime meridian and the date *
38 !* line. Also the poles. *
39 !* *
40 !* Error Codes: none *
41 !* *
42 !* Error Messages: none *
43 !* *
44 !************************************************************************
45 
46 ! use params_mod, only: DTR,ERAD,PI,RTD
47  IMPLICIT NONE
48  REAL*8 dtr/0.017453293 / ! degrees to radians
49  REAL*8 re / 6370.0/ ! radius of earth
50  REAL*8 pi /3.1415926/ ! pi
51  REAL*8 rtd /57.29577951 / ! radians to degrees
52 ! REAL*8 RZS /1786245696.0/ ! (geosynchronous height)**2
53  REAL*8 res /40589641.0 / ! (earth radius)**2
54  REAL*8 c1 /1826835337.0/ ! RES + RZS
55  REAL*8 c2 /538527888.0 / ! 2*RE*RES
56 
57  REAL rzs /1786245696.0/ ! (geosynchronous height)**2 for GOES
58 
59 ! REAL*8 A,B,C,COSD,COSE,E,P,PP
60  INTEGER, INTENT(IN):: i,j
61  REAL,INTENT(IN):: slon,rlat,rlon,slat
62  REAL,INTENT(OUT):: za
63 ! REAL C1,C2,RES,RE
64  REAL a,b,c,cosd,cose,e,p,pp
65 
66 ! RE=ERAD/1.0E3
67 ! RES=RE**2.0
68 ! C1=RES+RZS
69 ! C2=2.0*RE*RES/1000.
70 
71  a = (90.0 - rlat) * dtr ! colatitude of point
72  b = (90.0 - slat) * dtr ! colatitude of satellite
73 
74  IF(rlon>180.)THEN
75  c = abs(rlon- 360. - slon) * dtr
76  ELSE
77  c = abs(rlon - slon) * dtr
78  END IF
79 
80  cosd = cos(a)*cos(b) + sin(a)*sin(b)*cos(c) ! great circle arc
81 
82  pp = c1 - c2*cosd
83  p = sqrt(pp)
84 
85  cose = (pp + res - rzs) / (2.*re*p)
86  cose=max(min(cose,1.),-1.)
87  e = acos(cose)
88 
89  za = pi - e
90  za = za * rtd
91  za=max(za,0.)
92  if(abs(rlon-360.-slon)<1. .and. abs(rlat-30.)<1.)print*,'Debug GEO_ZENITH', &
93  rlon,rlat,res,c1,c2,a,b,c,cosd,pp,p,cose,e,za
94 
95  RETURN
96  END
97