cga/Algebra/Polygon.hs

63 lines
1.5 KiB
Haskell
Raw Normal View History

2015-01-08 00:41:14 +00:00
{-# OPTIONS_HADDOCK ignore-exports #-}
module Algebra.Polygon where
import Algebra.Vector
import Data.Maybe
import Diagrams.TwoD.Types
2015-01-08 00:41:14 +00:00
import MyPrelude
2015-01-09 03:01:43 +00:00
-- |Split a polygon by a given segment which must be vertices of the
-- polygon (returns empty array otherwise).
splitPoly :: [P2]
-> (P2, P2)
-> [[P2]]
2015-01-08 00:41:14 +00:00
splitPoly pts (a, b)
| elem a pts && elem b pts =
[b : takeWhile (/= b) shiftedPoly, a : dropWhile (/= b) shiftedPoly]
| otherwise = [[]]
where
shiftedPoly = shiftM' a pts
2015-01-09 03:01:43 +00:00
-- |Get all edges of a polygon.
polySegments :: [P2] -> [(P2, P2)]
2015-01-08 00:41:14 +00:00
polySegments p@(x':_:_:_) = go p ++ [(last p, x')]
where
go (x:y:xs) = (x, y) : go (y:xs)
go _ = []
polySegments _ = []
2015-01-09 02:20:13 +00:00
2015-01-09 03:01:43 +00:00
-- |Check whether the given segment is inside the polygon.
-- This doesn't check for segments that are completely outside
-- of the polygon yet.
isInsidePoly :: [P2] -> (P2, P2) -> Bool
2015-01-09 02:20:13 +00:00
isInsidePoly pts seg =
null
. catMaybes
. fmap (intersectSeg'' seg)
$ polySegments pts
2015-01-09 03:01:43 +00:00
-- |Check whether two points are adjacent vertices of a polygon.
adjacent :: P2 -> P2 -> [P2] -> Bool
adjacent u v = any (\x -> x == (u, v) || x == (v, u)) . polySegments
2015-01-09 03:01:43 +00:00
-- |Check whether the polygon is a triangle polygon.
isTrianglePoly :: [P2] -> Bool
isTrianglePoly [_, _, _] = True
isTrianglePoly _ = False
2015-01-09 03:01:43 +00:00
-- |Get all triangle polygons.
triangleOnly :: [[P2]] -> [[P2]]
triangleOnly = filter isTrianglePoly
2015-01-09 03:01:43 +00:00
-- |Get all non-triangle polygons.
nonTriangleOnly :: [[P2]] -> [[P2]]
nonTriangleOnly = filter (not . isTrianglePoly)