module Algorithms.Geometry.EuclideanMST.EuclideanMST where
import Algorithms.Geometry.DelaunayTriangulation.DivideAndConqueror
import Algorithms.Geometry.DelaunayTriangulation.Types
import Algorithms.Graph.MST
import Control.Lens
import Data.Ext
import Data.Geometry
import Data.Geometry.Ipe
import qualified Data.List.NonEmpty as NonEmpty
import Data.PlaneGraph
import Data.Proxy
import Data.Tree
euclideanMST :: (Ord r, Fractional r)
=> NonEmpty.NonEmpty (Point 2 r :+ p) -> Tree (Point 2 r :+ p)
euclideanMST pts = (\v -> g^.vDataOf v) <$> t
where
g = withEdgeDistances squaredEuclideanDist . toPlaneGraph (Proxy :: Proxy MSTW)
. delaunayTriangulation $ pts
t = mst g
data MSTW
drawTree' :: IpeOut (Tree (Point 2 r :+ p)) (IpeObject r)
drawTree' = IpeOut $
asIpeGroup . map (asIpeObject' mempty . uncurry ClosedLineSegment) . treeEdges
treeEdges :: Tree a -> [(a,a)]
treeEdges (Node v chs) = map ((v,) . rootLabel) chs ++ concatMap treeEdges chs