source: codes/icosagcm/trunk/src/sphere/spherical_geom.f90

Last change on this file was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

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