source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/DYNAMICO/src/sphere/spherical_geom.f90 @ 6612

Last change on this file since 6612 was 6612, checked in by acosce, 10 months ago

DYNAMICO used for ICOLMDZORINCA_CO2_Transport_GMD_2023

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