source: codes/icosagcm/branches/SATURN_DYNAMICO/ICOSAGCM/src/spherical_geom.f90 @ 267

Last change on this file since 267 was 267, checked in by ymipsl, 10 years ago

Synchronize trunk and Saturn branch.
Merge modification from trunk branch to Saturn branch.

YM

File size: 6.1 KB
Line 
1MODULE spherical_geom_mod
2USE genmod
3
4
5
6CONTAINS
7
8
9
10
11SUBROUTINE lonlat2xyz(lon,lat,xyz)
12IMPLICIT NONE
13  REAL(rstd),INTENT(IN) :: lon
14  REAL(rstd),INTENT(IN) :: lat
15  REAL(rstd),INTENT(OUT) :: xyz(3)
16 
17  xyz(1)=cos(lon)*cos(lat)
18  xyz(2)=sin(lon)*cos(lat)
19  xyz(3)=sin(lat)
20
21END SUBROUTINE lonlat2xyz
22
23
24SUBROUTINE xyz2lonlat(xyz,lon,lat)
25IMPLICIT NONE
26  REAL(rstd),INTENT(IN) :: xyz(3)
27  REAL(rstd),INTENT(OUT) :: lon
28  REAL(rstd),INTENT(OUT) :: lat
29 
30  REAL(rstd) :: coslat
31  REAL(rstd) :: xyzn(3)
32 
33  xyzn(:)=xyz(:)/sqrt(sum(xyz(:)**2))
34 
35  lat=asin(xyzn(3))
36  lon=atan2(xyzn(2),xyzn(1))
37END SUBROUTINE xyz2lonlat
38
39! lat/lon with respect to a displaced pole (rotated basis) :
40!  ( cos(lon0)*sin(lat0), sin(lon0)*sin(lat0), -cos(lat0))
41!  (-sin(lon0),           cos(lon0),           0)
42!  ( cos(lon0)*cos(lat0), sin(lon0)*cos(lat0), sin(lat0))
43
44SUBROUTINE lonlat2xyz_relative(lon,lat,lon0,lat0, xyz)
45IMPLICIT NONE
46  REAL(rstd),INTENT(IN) :: lon0, lat0, lon,lat
47  REAL(rstd),INTENT(OUT) :: xyz(3)
48  REAL(rstd) :: xx,yy,zz
49  xx = cos(lon)*cos(lat)
50  yy = sin(lon)*cos(lat)
51  zz = sin(lat)
52  xyz(1) = cos(lon0)*(sin(lat0)*xx+cos(lat0)*zz)-sin(lon0)*yy
53  xyz(2) = sin(lon0)*(sin(lat0)*yy+cos(lat0)*zz)+cos(lon0)*yy
54  xyz(3) = sin(lat0)*zz-cos(lat0)*xx
55END SUBROUTINE lonlat2xyz_relative
56
57SUBROUTINE xyz2lonlat_relative(xyz,lon0,lat0, lon,lat)
58IMPLICIT NONE
59  REAL(rstd),INTENT(IN) :: xyz(3), lon0, lat0
60  REAL(rstd),INTENT(OUT) :: lon,lat
61  REAL(rstd) :: xx,yy,zz
62  xx = sin(lat0)*(xyz(1)*cos(lon0)+xyz(2)*sin(lon0))-cos(lat0)*xyz(3)
63  yy = xyz(2)*cos(lon0)-xyz(1)*sin(lon0)
64  zz = cos(lat0)*(xyz(1)*cos(lon0)+xyz(2)*sin(lon0))+sin(lat0)*xyz(3)
65  lon = atan2(yy,xx)
66  lat = asin(zz)
67END SUBROUTINE xyz2lonlat_relative
68
69SUBROUTINE schmidt_transform(xyz,cc, lon0, lat0)
70  ! Based on formula (12) from Guo & Drake, JCP 2005
71  IMPLICIT NONE
72  REAL(rstd),INTENT(INOUT) :: xyz(3)
73  REAL(rstd), INTENT(IN) :: cc, lon0, lat0  ! stretching factor>0, lon/lat of zoomed area
74  REAL(rstd) :: lat,lon,mu
75  CALL xyz2lonlat_relative(xyz,lon0,lat0, lon,lat)
76  mu = sin(lat)
77  mu = ((cc-1)+mu*(cc+1)) / ((cc+1)+mu*(cc-1))
78  lat = asin(mu)
79  CALL lonlat2xyz_relative(lon,lat, lon0,lat0, xyz)
80END SUBROUTINE schmidt_transform
81
82SUBROUTINE dist_cart(A,B,d)
83USE vector
84IMPLICIT NONE
85  REAL(rstd),INTENT(IN)  :: A(3)
86  REAL(rstd),INTENT(IN)  :: B(3)
87  REAL(rstd),INTENT(OUT) :: d
88 
89   REAL(rstd)  :: n(3)
90   CALL cross_product2(A,B,n)
91   d=asin(sqrt(sum(n**2)))
92
93END SUBROUTINE dist_cart
94
95
96SUBROUTINE dist_lonlat(lonA,latA,lonB,latB,d)
97IMPLICIT NONE
98  REAL(rstd),INTENT(IN)  :: lonA
99  REAL(rstd),INTENT(IN)  :: latA
100  REAL(rstd),INTENT(IN)  :: lonB
101  REAL(rstd),INTENT(IN)  :: latB
102  REAL(rstd),INTENT(OUT) :: d
103 
104  d=acos(MAX(MIN(sin(latA)*sin(latB)+cos(latA)*cos(latB)*cos(lonA-lonB),1.),-1.))
105 
106END SUBROUTINE dist_lonlat
107
108SUBROUTINE surf_triangle(A,B,C,surf)
109  REAL(rstd),INTENT(IN)  :: A(3)
110  REAL(rstd),INTENT(IN)  :: B(3)
111  REAL(rstd),INTENT(IN)  :: C(3)
112  REAL(rstd),INTENT(OUT) :: Surf
113
114  REAL(rstd)  :: AB,AC,BC
115  REAL(rstd)  :: s,x
116 
117  CALL dist_cart(A,B,AB)
118  CALL dist_cart(A,C,AC)
119  CALL dist_cart(B,C,BC)
120 
121  s=(AB+AC+BC)/2
122  x=tan(s/2) * tan((s-AB)/2)  * tan((s-AC)/2) * tan((s-BC)/2)
123  IF (x<0) x=0.
124  surf=4*atan(sqrt( x))
125 
126END SUBROUTINE surf_triangle 
127
128
129SUBROUTINE div_arc(A,B,frac,C)
130IMPLICIT NONE
131  REAL(rstd),INTENT(IN)  :: A(3)
132  REAL(rstd),INTENT(IN)  :: B(3)
133  REAL(rstd),INTENT(IN)  :: frac
134  REAL(rstd),INTENT(OUT)  :: C(3)
135 
136  REAL(rstd) :: d
137  REAL(rstd) :: M(3,3)
138  REAL(rstd) :: alpha(3,3)
139  INTEGER    :: IPIV(3)
140  INTEGER    :: info
141  REAL(rstd) :: xa,xb,xc
142  REAL(rstd) :: ya,yb,yc
143  REAL(rstd) :: za,zb,zc
144  REAL(rstd) :: alpha_A,alpha_B,alpha_C
145  REAL(rstd) :: x,y,z
146  REAL(rstd) :: a1,a2,a3
147  REAL(rstd) :: b1,b2,b3
148 
149 
150  xa=A(1) ; ya=A(2) ; za=A(3)
151  xb=B(1) ; yb=B(2) ; zb=B(3)
152
153  CALL dist_cart(A,B,d)
154
155  C(1)=cos(frac*d) 
156  C(2)=cos((1-frac)*d)
157  C(3)=0.
158
159  xc=ya*zb-yb*za ; yc=-(xa*zb-xb*za) ; zc=xa*yb-xb*ya
160 
161  M(1,1)=xa ; M(1,2)=ya ; M(1,3)=za
162  M(2,1)=xb ; M(2,2)=yb ; M(2,3)=zb
163  M(3,1)=xc ; M(3,2)=yc ; M(3,3)=zc
164  stop 'STOP'
165!  CALL DGESV(3,1,M,3,IPIV,C,3,info)
166 
167END SUBROUTINE div_arc
168
169SUBROUTINE div_arc_bis(A,B,frac,C)
170IMPLICIT NONE
171  REAL(rstd),INTENT(IN)  :: A(3)
172  REAL(rstd),INTENT(IN)  :: B(3)
173  REAL(rstd),INTENT(IN)  :: frac
174  REAL(rstd),INTENT(OUT)  :: C(3)
175 
176   C=A*(1-frac)+B*frac 
177   C=C/sqrt(sum(C**2))
178END SUBROUTINE div_arc_bis
179
180
181  SUBROUTINE circumcenter(A0,B0,C0,center)
182  USE vector
183  IMPLICIT NONE
184    REAL(rstd), INTENT(IN)  :: A0(3),B0(3),C0(3)
185    REAL(rstd), INTENT(OUT) :: Center(3)
186   
187    REAL(rstd)  :: a(3),b(3),c(3), ac(3), ab(3), p1(3), q(3), p2(3)
188   
189    a=A0/sqrt(sum(A0**2))
190    b=B0/sqrt(sum(B0**2))
191    c=C0/sqrt(sum(C0**2))
192   
193    ab=b-a
194    ac=c-a
195    CALL Cross_product2(ab,ac,p1)
196    IF(.FALSE.) THEN ! Direct solution, round-off error
197       center=p1/norm(p1)
198    ELSE ! Two-step solution, stable
199       q = SUM(ac**2)*ab-SUM(ab**2)*ac
200       CALL Cross_product2(p1,q,p2)
201       p2 = a + p2/(2.*SUM(p1**2))
202       center = p2/norm(p2)
203    END IF
204  END SUBROUTINE circumcenter
205   
206
207  SUBROUTINE compute_centroid(points,n,centr)
208  USE vector
209  IMPLICIT NONE
210    INTEGER :: n
211    REAL(rstd), INTENT(IN)  :: points(3,n)
212    REAL(rstd), INTENT(OUT) :: Centr(3)
213   
214    REAL(rstd) :: p1(3),p2(3),cross(3), cc(3)
215    REAL(rstd) :: norm_cross, area
216    INTEGER :: i,j
217
218    centr(:)=0
219    IF(.FALSE.) THEN 
220       ! Gauss formula (subject to round-off error)
221       DO i=1,n
222          j=MOD(i,n)+1
223          p1=points(:,i)/norm(points(:,i))
224          p2=points(:,j)/norm(points(:,j))
225          CALL cross_product2(p1,p2,cross)
226          norm_cross=norm(cross)
227          if (norm_cross<1e-10) CYCLE
228          centr(:)=centr(:)+asin(norm_cross)*cross(:)/norm_cross
229       ENDDO       
230    ELSE
231       ! Simple area-weighted average (second-order accurate, stable)
232       cc=SUM(points,2) ! arithmetic average used as center
233       cc=cc/norm(cc)
234       DO i=1,n
235          j=MOD(i,n)+1
236          p1=points(:,i)/norm(points(:,i))
237          p2=points(:,j)/norm(points(:,j))
238          CALL surf_triangle(cc,p1,p2,area)
239          centr(:)=centr(:)+area*(p1+p2+cc)
240       ENDDO
241    END IF
242   
243    centr(:)=centr(:)/norm(centr(:))
244
245  END SUBROUTINE compute_centroid
246
247END MODULE spherical_geom_mod
248
249
Note: See TracBrowser for help on using the repository browser.