-- | This module describes what lines are defines functions to work -- with lines. module Geom2d.Line ( -- * Infinite lines InfLine , mkInfLine , lineF , parallel , slope , root , intersection -- * Finite lines , FinLine , mkFinLine , lineLength ) where import Geom2d.Point import Geom2d.Line.Internal -- | Construct an infinit line by specifiying two points. We won't -- get a line when the given points are equal. mkInfLine :: (Eq (p a)) => p a -> p a -> Maybe (InfLine p a) mkInfLine a b | a == b = Nothing | otherwise = Just $ InfLine a b -- | Get a function describing the line. We won't get a function if -- the line is vertical. lineF :: (Eq a, Fractional a, Point p) => InfLine p a -> Maybe (a -> a) lineF l@(InfLine p _) = ( \m -> case root l of Just x0 -> \arg -> m * (arg - x0) Nothing -> const (y p) ) <$> slope l -- | Check if two lines are paralllel to each other. This function -- assumes lines parallel to themselves. parallel :: (Num a, Num (p a), Point p, Eq a) => InfLine p a -> InfLine p a -> Bool parallel (InfLine a b) (InfLine p q) = (b - a) `cross` (q - p) == 0 -- | Calculate the slope of a line. We won't get a value for the -- slope if, and only if, the line is vertical. slope :: (Fractional a, Point p, Eq a) => InfLine p a -> Maybe a slope (InfLine p q) | x p == x q = Nothing | otherwise = Just $ (y q - y p) / (x q - x p) -- | Calculate the point where a line meets the x-axis. We won't get -- a value if, and only if the line is parallel to the x-axis. root :: (Eq a, Fractional a, Point p) => InfLine p a -> Maybe a root l@(InfLine p _) = case slope l of Nothing -> Just $ x p Just m -> if m == 0 then Nothing else Just $ x p - (y p * m) -- | Calculate the point where two lines intersect. intersection :: (Eq (p a), Num (p a), RealFloat a, Point p) => InfLine p a -> InfLine p a -> Maybe (p a) intersection l1@(InfLine a1 _) l2@(InfLine b1 _) | l1 == l2 = Nothing | l1 `parallel` l2 = Nothing | otherwise = case slope l1 of Nothing -> do x0 <- root l1 f <- lineF l2 return (fromCoords x0 (f x0)) Just ma -> case slope l2 of Nothing -> do x0 <- root l2 f <- lineF l1 return (fromCoords x0 (f x0)) Just mb -> do let na = y a1 - ma * x a1 nb = y b1 - mb * x b1 safeDiv num denom | denom == 0 = Nothing | otherwise = Just (num/denom) x' <- (nb - na) `safeDiv` (ma - mb) f <- lineF l1 return (fromCoords x' (f x')) -- | mkFinLine returns a valid finite line, if any. mkFinLine :: (Eq (p a)) => p a -> p a -> Maybe (FinLine p a) mkFinLine a b | a == b = Nothing | otherwise = Just (FinLine a b) -- | Get the length of a finite line. lineLength :: (Point p, Num (p a), Floating a) => FinLine p a -> a lineLength (FinLine a b) = magnitude (b - a)