module Algorithms.Geometry.PolyLineSimplification.DouglasPeucker where
import Control.Lens hiding (only)
import Data.Ext
import qualified Data.Foldable as F
import Data.Geometry.LineSegment
import Data.Geometry.Point
import Data.Geometry.PolyLine
import Data.Geometry.Vector
import qualified Data.LSeq as LSeq
import Data.LSeq (LSeq, pattern (:|>))
import Data.Ord (comparing)
douglasPeucker :: (Ord r, Fractional r, Arity d)
=> r -> PolyLine d p r -> PolyLine d p r
douglasPeucker eps pl
| dst <= (eps*eps) = fromPointsUnsafe [a,b]
| otherwise = douglasPeucker eps pref `merge` douglasPeucker eps subf
where
pts = pl^.points
a = LSeq.head pts
b = LSeq.last pts
(i,dst) = maxDist pts (ClosedLineSegment a b)
(pref,subf) = split i pl
merge :: PolyLine d p r -> PolyLine d p r -> PolyLine d p r
merge pref sub = PolyLine $ pref' `append` (sub^.points)
where
(pref' :|> _) = pref^.points
append :: LSeq.LSeq n a -> LSeq.LSeq m a -> LSeq.LSeq m a
append a b = LSeq.promise $ LSeq.append a b
split :: Int -> PolyLine d p r
-> (PolyLine d p r, PolyLine d p r)
split i (PolyLine pts) = bimap f f (as,bs)
where
f = PolyLine . LSeq.forceLSeq (C :: C 2)
as = LSeq.take (i+1) pts
bs = LSeq.drop i pts
maxDist :: (Ord r, Fractional r, Arity d)
=> LSeq n (Point d r :+ p) -> LineSegment d p r -> (Int,r)
maxDist pts s = F.maximumBy (comparing snd) . LSeq.mapWithIndex (\i (p :+ _) ->
(i,sqDistanceToSeg p s)) $ pts