{-# LANGUAGE UnicodeSyntax #-} module Numeric.Geometric.Predicates.Rational where import Numeric.Geometric.Primitives -- | Counter-clockwise orientation test. Classifies p3 in relation to the line formed by p1 and p2. ccw ∷ Vector2 Rational → Vector2 Rational → Vector2 Rational → Ordering -- ^ LT=Right, GT=Left, EQ=Coincident ccw (x1,y1) (x2,y2) (x3,y3) = compare result 0 where result = (x1*y2) + (x2*y3) + (x3*y1) - (x1*y3) - (x2*y1) - (x3*y2) -- | Test the relation of a point to the circle formed by (p1..p3). incircle ∷ (Vector2 Rational, Vector2 Rational, Vector2 Rational) -- ^ 3 points on the circle, must be in counterclockwise order. → Vector2 Rational -- ^ Query point → Ordering -- ^ GT=inside, EQ=border, LT=outside incircle (p1,p2,p3) p4 = compare result 0 where result = (d p1) * (ccw' p2 p3 p4) - (d p2) * (ccw' p1 p3 p4) + (d p3) * (ccw' p1 p2 p4) - (d p4) * (ccw' p1 p2 p3) d (x,y) = (x*x) + (y*y) ccw' (x1,y1) (x2,y2) (x3,y3) = (x1*y2) + (x2*y3) + (x3*y1) - (x1*y3) - (x2*y1) - (x3*y2) -- | Test if Point is within the closed interval specified cintt ∷ Rational -- ^ Lo → Rational -- ^ Hi → Rational -- ^ Point → Bool cintt x1 x2 p | x1 == x2 = p == x1 | otherwise = t >= 0 && t <= 1 where t = (u - p) / (-v) u = x1 v = x2 - x1 -- | Calculate the point of intersecton. Assumes the input lines are already known to be intersecting, isctp ∷ LineSegment (Vector2 Rational) → LineSegment (Vector2 Rational) → Vector2 Rational isctp ((ax,ay),(bx,by)) ((cx,cy),(dx,dy)) = (x,y) where rtop = (ay-cy)*(dx-cx)-(ax-cx)*(dy-cy) rbot = (bx-ax)*(dy-cy)-(by-ay)*(dx-cx) r = rtop/rbot x = ax + r * (bx - ax) y = ay + r * (by - ay)