GRIDMAN
grid managment library
geom.f
Go to the documentation of this file.
1 C> @file geom.f
2 C> Basic geometrical calculations
3 C GRIDMAN, grid managment library. Author: Vladislav Kotov, v.kotov@fz-juelich.de
4 
5 ! Copyright (c) 2017 Forschungszentrum Juelich GmbH
6 ! Vladislav Kotov
7 !
8 ! This file is part of GRIDMAN.
9 !
10 ! GRIDMAN is free software: you can redistribute it and/or modify
11 ! it under the terms of the GNU General Public License as published by
12 ! the Free Software Foundation, either version 3 of the License, or
13 ! (at your option) any later version.
14 !
15 ! GRIDMAN is distributed in the hope that it will be useful,
16 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
17 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
18 ! GNU General Public License for more details.
19 !
20 ! You should have received a copy of the GNU General Public License
21 ! along with GRIDMAN. If not, see <http://www.gnu.org/licenses/>.
22 
23 C> Area of a triangle
24  FUNCTION gridman_triaarea(X1,Y1,X2,Y2,X3,Y3)
25 
26  USE gridman,ONLY:gridman_dp
27  IMPLICIT NONE
28  INTRINSIC abs
29 
30  REAL(GRIDMAN_DP),INTENT(IN) :: X1,Y1,X2,Y2,X3,Y3
31  REAL(GRIDMAN_DP) :: GRIDMAN_TRIAAREA,S
32 
33  s=x1*(y2-y3)+x2*(y3-y1)+x3*(y1-y2)
34  gridman_triaarea=0.5*abs(s)
35 
36  END FUNCTION gridman_triaarea
37 
38 
39 C> Volume of the solid of revolution obtained by
40 !! rotating of a triangle around axis X=0
41  FUNCTION gridman_triavol(X1,Y1,X2,Y2,X3,Y3)
42 
44  IMPLICIT NONE
45 
46  REAL(GRIDMAN_DP),INTENT(IN) :: X1,Y1,X2,Y2,X3,Y3
47  REAL(GRIDMAN_DP) :: GRIDMAN_TRIAVOL,GRIDMAN_TRIAAREA
48  REAL(GRIDMAN_DP),PARAMETER :: PI3=gridman_2pi/3.0
49 
50  gridman_triavol=pi3*(x1+x2+x3)*
51  * gridman_triaarea(x1,y1,x2,y2,x3,y3)
52 
53  END FUNCTION gridman_triavol
54 
55 
56 C> Distance between two points on a plane
57  FUNCTION gridman_dist2d(X1,Y1,X2,Y2)
58 
59  USE gridman,ONLY:gridman_dp
60  IMPLICIT NONE
61  INTRINSIC sqrt
62 
63  REAL(GRIDMAN_DP),INTENT(IN) :: X1,Y1,X2,Y2
64  REAL(GRIDMAN_DP) :: GRIDMAN_DIST2D
65 
66  gridman_dist2d=sqrt((x1-x2)**2+(y1-y2)**2)
67 
68  END FUNCTION gridman_dist2d
69 
70 
71 C> Vector (XY,YN) normal to (X0,Y0)
72  SUBROUTINE gridman_norm2d(X0,Y0,XN,YN)
73 
74  USE gridman,ONLY:gridman_dp
75  IMPLICIT NONE
76 
77  REAL(GRIDMAN_DP),INTENT(IN) :: X0,Y0
78  REAL(GRIDMAN_DP),INTENT(OUT) :: XN,YN
79 
80  xn=-y0
81  yn=x0
82 
83  END SUBROUTINE gridman_norm2d
84 
85 
86 C> Area of the conical surface obtained by rotation
87 !! of the interval (X1,Y1),(X2,Y2) around X=0
88  FUNCTION gridman_conarea(X1,Y1,X2,Y2)
89 
91  IMPLICIT NONE
92  INTRINSIC sqrt
93 
94  REAL(GRIDMAN_DP),INTENT(IN) :: X1,Y1,X2,Y2
95  REAL(GRIDMAN_DP) :: GRIDMAN_CONAREA
96 
97  gridman_conarea=gridman_pi*(x1+x2)*sqrt((x1-x2)**2+(y1-y2)**2)
98 
99  END FUNCTION gridman_conarea
100 
101 C> Intersection of "particle trajectory" with an interval (2D)
102 C>
103 C> Find a point where a "particle" with velocity (VX0,VY0) which starts
104 !! from point (X0,Y0) intersects the interval [(X1,Y1)(X2,Y2)].
105 !! The function returns .TRUE. if intersection exist
106 !! and .FALSE. otherwise
107  FUNCTION gridman_cross2d(X0,Y0,V,U,X1,Y1,X2,Y2,XI,YI)
109  IMPLICIT NONE
110  INTRINSIC abs,tiny
111 
112 C> X-coordinate of the "particle" starting point
113  REAL(GRIDMAN_DP),INTENT(IN) :: X0
114 C> Y-coordinate of the "particle" starting point
115  REAL(GRIDMAN_DP),INTENT(IN) :: Y0
116 C> X-component of the particle velocity
117  REAL(GRIDMAN_DP),INTENT(IN) :: V
118 C> Y-component of the particle velocity
119  REAL(GRIDMAN_DP),INTENT(IN) :: U
120 C> X-coordinate of the first end of the interval
121  REAL(GRIDMAN_DP),INTENT(IN) :: X1
122 C> Y-coordinate of the first end of the interval
123  REAL(GRIDMAN_DP),INTENT(IN) :: Y1
124 C> X-coordinate of the second end of the interval
125  REAL(GRIDMAN_DP),INTENT(IN) :: X2
126 C> Y-coordinate of the second end of the interval
127  REAL(GRIDMAN_DP),INTENT(IN) :: Y2
128 C> X-coordinate of the intersection point
129  REAL(GRIDMAN_DP),INTENT(OUT) :: XI
130 C> Y-coordinate of the intersection point
131  REAL(GRIDMAN_DP),INTENT(OUT) :: YI
132  LOGICAL GRIDMAN_CROSS2D
133 
134  REAL(GRIDMAN_DP) :: D,T
135 
136  d=v*(y2-y1)+u*(x1-x2)
137  IF(abs(d).LT.10.*tiny(d)) THEN
138  gridman_cross2d=.false.
139  RETURN
140  END IF
141  t=x1*y2-x2*y1+(y1-y2)*x0+(x2-x1)*y0
142  t=t/d
143  IF(.NOT.t.GT.0.) THEN !WRONG DIRECTION
144  gridman_cross2d=.false.
145  RETURN
146  END IF
147  xi=x0+v*t
148  yi=y0+u*t
149 
150  IF( ( xi.GT.x1.AND.xi.GT.x2 ) .OR. !INTERSECTION POINT IS
151  f ( xi.LT.x1.AND.xi.LT.x2 ) .OR.
152  f ( yi.GT.y1.AND.yi.GT.y2 ) .OR. !OUTSIDE OF THE INTERVAL
153  f ( yi.LT.y1.AND.yi.LT.y2 ) ) THEN
154  gridman_cross2d=.false.
155  ELSE
156  gridman_cross2d=.true.
157  END IF
158 
159  END FUNCTION gridman_cross2d
160 
161 C> Intersection of two intervals on a plane
162 C>
163 C> Find intersection point of two intervals on a plane.
164 !! The function returns .TRUE. if intersection exist and .FALSE. otherwise
165  FUNCTION gridman_intersect2d(X11,Y11,X12,Y12,
166  f x21,y21,x22,y22,xi,yi)
168  IMPLICIT NONE
169  INTRINSIC tiny,abs
170 
171 C> X-coordinate of the first end of the first interval
172  REAL(GRIDMAN_DP),INTENT(IN) :: X11
173 C> Y-coordinate of the first end of the first interval
174  REAL(GRIDMAN_DP),INTENT(IN) :: Y11
175 C> X-coordinate of the second end of the first interval
176  REAL(GRIDMAN_DP),INTENT(IN) :: X12
177 C> Y-coordinate of the second end of the first interval
178  REAL(GRIDMAN_DP),INTENT(IN) :: Y12
179 C> X-coordinate of the first end of the second interval
180  REAL(GRIDMAN_DP),INTENT(IN) :: X21
181 C> Y-coordinate of the first end of the second interval
182  REAL(GRIDMAN_DP),INTENT(IN) :: Y21
183 C> X-coordinate of the second end of the second interval
184  REAL(GRIDMAN_DP),INTENT(IN) :: X22
185 C> Y-coordinate of the second end of the second interval
186  REAL(GRIDMAN_DP),INTENT(IN) :: Y22
187 C> X-coordinate of the intersection point
188  REAL(GRIDMAN_DP),INTENT(OUT) :: XI
189 C> Y-coordinate of the intersection point
190  REAL(GRIDMAN_DP),INTENT(OUT) :: YI
191  LOGICAL :: GRIDMAN_INTERSECT2D
192 
193  REAL(GRIDMAN_DP) :: A1,B1,C1,A2,B2,C2,DET
194 
195  a1=y12-y11
196  b1=x11-x12
197  c1=y11*(x12-x11)-x11*(y12-y11)
198  a2=y22-y21
199  b2=x21-x22
200  c2=y21*(x22-x21)-x21*(y22-y21)
201  det=a1*b2-a2*b1
202  IF(abs(det).GT.tiny(det)) THEN
203  det=1/det
204  xi=(b1*c2-b2*c1)*det
205  yi=(c1*a2-c2*a1)*det
206 C CHECK IF THE POINT IS OUT OF THE 1st INTERVAL
207  IF(abs(a1).GT.abs(b1)) THEN
208 C Y-PROJECTION OF THE 1st INTERVAL IS LARGER
209  IF( ( yi.GT.y11.AND.yi.GT.y12 ) .OR.
210  f ( yi.LT.y11.AND.yi.LT.y12 ) ) THEN
211  gridman_intersect2d=.false.
212  RETURN
213  END IF
214  ELSE
215 C X-PROJECTION OF THE 1st INTERVAL IS LARGER
216  IF( ( xi.GT.x11.AND.xi.GT.x12 ) .OR.
217  f ( xi.LT.x11.AND.xi.LT.x12 ) ) THEN
218  gridman_intersect2d=.false.
219  RETURN
220  END IF
221  END IF
222 C CHECK IF THE POINT IS OUT OF THE 2nd INTERVAL
223  IF(abs(a2).GT.abs(b2)) THEN
224 C Y-PROJECTION OF THE 2ndT INTERVAL IS LARGER
225  IF( ( yi.GT.y21.AND.yi.GT.y22 ) .OR.
226  f ( yi.LT.y21.AND.yi.LT.y22 )) THEN
227  gridman_intersect2d=.false.
228  RETURN
229  END IF
230  ELSE
231 C X-PROJECTION OF THE 2nd INTERVAL IS LARGER
232  IF( ( xi.GT.x21.AND.xi.GT.x22 ) .OR.
233  f ( xi.LT.x21.AND.xi.LT.x22 )) THEN
234  gridman_intersect2d=.false.
235  RETURN
236  END IF
237  END IF
238  gridman_intersect2d=.true.
239  ELSE
240  gridman_intersect2d=.false. !PARALLEL LINES
241  END IF
242 
243  END FUNCTION gridman_intersect2d
244 
245 C> Find if point lies inside a closed polygon
246 C>
247 C> The function returns .TRUE. if the point (X0,Y0) lies inside the
248 C> polygon (XP,YP) and .FALSE. otherwise
249 C>
250 C> It is assumed that the polygon is simple and closed.
251 C> That is, no intesection between polygon edges, first and
252 C> last vertex of the polygon are the same.
253 C>
254 C> WARNING: this function does not check that the polygon is
255 C> simple and closed
256 C>
257 C> Crossing number method - even-odd test - is applied
258  FUNCTION gridman_point_in_polygon(XP,YP,NP,X0,Y0)
260  IMPLICIT NONE
261  INTRINSIC tiny,abs,mod
262 
263 C> Number of the polygon vertices - first and last vertex is counted twice
264  INTEGER(GRIDMAN_SP),INTENT(IN) :: NP
265 C> X-coordinates of the vertices
266  REAL(GRIDMAN_DP) :: XP(np)
267 C> Y-coordinates of the vertices
268  REAL(GRIDMAN_DP) :: YP(np)
269 C> X-coordinate of the point to be checked
270  REAL(GRIDMAN_DP) :: X0
271 C> Y-coordinate of the point to be checked
272  REAL(GRIDMAN_DP) :: Y0
273 
274  LOGICAL :: GRIDMAN_POINT_IN_POLYGON
275 
276  REAL(GRIDMAN_DP) :: Y1,Y2,DY,X1,X2,DX,XI
277  INTEGER(GRIDMAN_SP) :: IP,CN
278 
279 C COUNT INTERSECTIONS OF POLYGON WITH THE HORIZONTAL RAY
280 C DRAWN FROM THE POINT (X0,Y0) TO THE RIGHT
281  cn=0
282  DO ip=1,np-1
283  y1=yp(ip)
284  y2=yp(ip+1)
285  dy=y2-y1
286  IF(.NOT.abs(dy).GT.10*tiny(dy)) cycle !JUST IN CASE ...
287  IF(dy.GT.0.) THEN
288 C POLYGON EDGE GOES UPWARDS
289  y1=y1-gridman_tol*abs(dy)
290  IF(y1.LT.y0.AND.y0.LT.y2) THEN
291  x1=xp(ip)
292  x2=xp(ip+1)
293  dx=x2-x1
294  xi=x1+dx/dy*(y0-y1)
295 C COUNT ONLY INTERSECTIONS TO THE RIGHT FROM THE CHECKED POINT
296  IF(xi.GT.x0) cn=cn+1
297  END IF
298  ELSEIF(dy.LT.0.) THEN
299 C POLYGON EDGE GOES DOWNWARDS
300  y2=y2-gridman_tol*abs(dy)
301  IF(y2.LT.y0.AND.y0.LT.y1) THEN
302  x1=xp(ip)
303  x2=xp(ip+1)
304  dx=x2-x1
305  xi=x1+dx/dy*(y0-y1)
306 C COUNT ONLY INTERSECTIONS TO THE RIGHT FROM THE CHECKED POINT
307  IF(xi.GT.x0) cn=cn+1
308  END IF
309  END IF
310  END DO
311 
312  IF(mod(cn,2).EQ.0) THEN
313  gridman_point_in_polygon=.false.
314  ELSE
315  gridman_point_in_polygon=.true.
316  END IF
317 
318  END FUNCTION gridman_point_in_polygon
319 
320 C> Find if point is close to the interval within prescribed tolerance
321 C>
322 C> Function returns .TRUE. if the point (X,Y) lies on the interval
323 C> [(X1,Y1),(X2,Y2)]) withing relative tolerance TOL and .FALSE. otherwise
324  FUNCTION gridman_close2interval2d(X1,Y1,X2,Y2,X,Y,TOL)
326  IMPLICIT NONE
327  INTRINSIC tiny,abs
328 
329 C> X-coordinate of the 1st end of the interval
330  REAL(GRIDMAN_DP),INTENT(IN) :: X1
331 C> Y-coordinate of the 1st end of the interval
332  REAL(GRIDMAN_DP),INTENT(IN) :: Y1
333 C> X-coordinate of the 2nd end of the interval
334  REAL(GRIDMAN_DP),INTENT(IN) :: X2
335 C> Y-coordinate of the 2nd end of the interval
336  REAL(GRIDMAN_DP),INTENT(IN) :: Y2
337 C> X-coordinate of the point to be checked
338  REAL(GRIDMAN_DP),INTENT(IN) :: X
339 C> Y-coordinate of the point to be checked
340  REAL(GRIDMAN_DP),INTENT(IN) :: Y
341 C> Tolerance parameter which defines relative accuracy, e.g. 1e-7
342  REAL(GRIDMAN_DP),INTENT(IN) :: TOL
343  LOGICAL :: GRIDMAN_CLOSE2INTERVAL2D
344 
345  REAL(GRIDMAN_DP) :: D,DX,DY,EPS
346 
347  dx=y2-y1
348  dy=x1-x2
349  d=abs(dx*x+dy*y+x2*y1-x1*y2)
350  eps=abs(dx*x)*tol+abs(dy*y)*tol+10.*tiny(x)
351  IF(d.LT.eps) THEN
352 C POINT (X,Y) IS CLOSE TO THE LINE DRAWN THROUGH (X1,Y1) AND(X2,Y2)
353  IF( abs(dy).GT.abs(dx) ) THEN
354 C X-PROJECTION OF [(X1,Y1),(X2,Y2)] IS LARGER THAN THE Y-PROJECTION
355 C CHECK THAN X IS IN THE INTERVAL [X1,X2]
356  eps=abs(x)*tol+10.*tiny(x)
357  IF( (x.GT.x1-eps.AND.x.LT.x2+eps).OR.
358  f (x.GT.x2-eps.AND.x.LT.x1+eps)) THEN
359 C X IN THE INTERVAL [X1,X2]
360  gridman_close2interval2d=.true.
361  ELSE
362  gridman_close2interval2d=.false.
363  END IF
364  ELSE
365 C Y-PROJECTION OF [(X1,Y1),(X2,Y2)] IS LARGER THAN THE X-PROJECTION
366 C CHECK THAN Y IS IN THE INTERVAL [Y1,Y2]
367  eps=abs(y)*tol+10.*tiny(y)
368  IF( (y.GT.y1-eps.AND.y.LT.y2+eps).OR.
369  f (y.GT.y2-eps.AND.y.LT.y1+eps)) THEN
370  gridman_close2interval2d=.true.
371  ELSE
372  gridman_close2interval2d=.false.
373  END IF
374  END IF
375  ELSE
376  gridman_close2interval2d=.false.
377  END IF
378 
379  END FUNCTION gridman_close2interval2d
logical function gridman_intersect2d(X11, Y11, X12, Y12, X21, Y21, X22, Y22, XI, YI)
Intersection of two intervals on a plane.
Definition: geom.f:167
logical function gridman_cross2d(X0, Y0, V, U, X1, Y1, X2, Y2, XI, YI)
Intersection of "particle trajectory" with an interval (2D)
Definition: geom.f:108
real(gridman_dp), save, public gridman_tol
Tolerance parameter which is used to compare two real numbers.
Definition: gridman.f:127
integer, parameter, public gridman_dp
Kind parameter for real numbers.
Definition: gridman.f:93
real(gridman_dp) function gridman_triavol(X1, Y1, X2, Y2, X3, Y3)
Volume of the solid of revolution obtained by rotating of a triangle around axis X=0.
Definition: geom.f:42
logical function gridman_close2interval2d(X1, Y1, X2, Y2, X, Y, TOL)
Find if point is close to the interval within prescribed tolerance.
Definition: geom.f:325
real(gridman_dp) function gridman_conarea(X1, Y1, X2, Y2)
Area of the conical surface obtained by rotation of the interval (X1,Y1),(X2,Y2) around X=0...
Definition: geom.f:89
logical function gridman_point_in_polygon(XP, YP, NP, X0, Y0)
Find if point lies inside a closed polygon.
Definition: geom.f:259
real(gridman_dp), parameter, public gridman_2pi
2PI number
Definition: gridman.f:108
real(gridman_dp) function gridman_triaarea(X1, Y1, X2, Y2, X3, Y3)
Area of a triangle.
Definition: geom.f:25
real(gridman_dp), parameter, public gridman_pi
PI number.
Definition: gridman.f:106
Definition of data types, global constants and variables.
Definition: gridman.f:83
real(gridman_dp) function gridman_dist2d(X1, Y1, X2, Y2)
Distance between two points on a plane.
Definition: geom.f:58
subroutine gridman_norm2d(X0, Y0, XN, YN)
Vector (XY,YN) normal to (X0,Y0)
Definition: geom.f:73
integer, parameter, public gridman_sp
Kind parameter for integer numbers.
Definition: gridman.f:95