{-# LANGUAGE ScopedTypeVariables #-}
module Algorithms.Geometry.LowerEnvelope.DualCH where
import Data.Maybe(fromJust)
import Control.Lens((^.))
import Data.Ext
import Data.Geometry
import Algorithms.Geometry.ConvexHull.GrahamScan
import Data.List.NonEmpty(NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import Data.Geometry.Duality
import Data.Vinyl.CoRec
type Envelope a r = NonEmpty (Line 2 r :+ a)
lowerEnvelope :: (Ord r, Fractional r) => NonEmpty (Line 2 r :+ a) -> Envelope a r
lowerEnvelope = NonEmpty.reverse . lowerEnvelopeWith upperHull
type UpperHullAlgorithm a r = NonEmpty (Point 2 r :+ a) -> NonEmpty (Point 2 r :+ a)
lowerEnvelopeWith :: (Fractional r, Eq r)
=> UpperHullAlgorithm (Line 2 r :+ a) r
-> NonEmpty (Line 2 r :+ a) -> Envelope a r
lowerEnvelopeWith chAlgo = fromPts . chAlgo . toPts
where
toPts = fmap (\l -> dualPoint' (l^.core) :+ l)
fromPts = fmap (^.extra)
vertices :: (Ord r, Fractional r) => Envelope a r -> [Point 2 r :+ (a,a)]
vertices e = zipWith intersect' (NonEmpty.toList e) (NonEmpty.tail e)
intersect' :: forall r a. (Ord r, Fractional r)
=> Line 2 r :+ a -> Line 2 r :+ a -> Point 2 r :+ (a,a)
intersect' (l :+ le) (r :+ re) = (:+ (le,re)) . fromJust
. asA @(Point 2 r) $ l `intersect` r