Copyright | (c) Stéphane Laurent 2023 |
---|---|
License | GPL-3 |
Maintainer | laurent_step@outlook.fr |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
See README for examples.
Synopsis
- class HasCenter m where
- class HasVolume m where
- class HasEdges m where
- class HasVertices m where
- class HasNormal m where
- class HasFamily m where
- data Family
- type EdgeMap = InsOrdHashMap IndexPair ([Double], [Double])
- data IndexPair = Pair Index Index
- type IndexSet = IntSet
- type IndexMap = IntMap
- type Index = Int
- verticesIds :: HasVertices a => a -> [Index]
- verticesCoordinates :: HasVertices a => a -> [[Double]]
- nVertices :: HasVertices a => a -> Int
- edgesIds :: HasEdges a => a -> [IndexPair]
- edgesIds' :: HasEdges a => a -> [(Index, Index)]
- edgesCoordinates :: HasEdges a => a -> [([Double], [Double])]
- nEdges :: HasEdges a => a -> Int
- isEdge :: HasEdges a => a -> (Index, Index) -> Bool
- toPoints :: HasEdges a => a -> (Index, Index) -> Maybe ([Double], [Double])
- toPoints' :: HasEdges a => a -> (Index, Index) -> ([Double], [Double])
- data ConvexHull = ConvexHull {
- _hvertices :: IndexMap Vertex
- _hfacets :: IntMap Facet
- _hridges :: IntMap Ridge
- _hedges :: EdgeMap
- _simplicial :: Bool
- _dimension :: Int
- data Facet = Facet {}
- data Ridge = Ridge {}
- data Vertex = Vertex {
- _point :: [Double]
- _neighfacets :: IntSet
- _neighvertices :: IndexSet
- _neighridges :: IntSet
- convexHull :: [[Double]] -> Bool -> Bool -> Maybe FilePath -> IO ConvexHull
- hullSummary :: ConvexHull -> String
- hullVolume :: ConvexHull -> Double
- edgeOf :: ConvexHull -> (Index, Index) -> [Int]
- facetRidges :: ConvexHull -> Facet -> IntMap Ridge
- facetsVerticesIds :: ConvexHull -> [[Index]]
- ridgesVerticesIds :: ConvexHull -> [[Index]]
- groupedFacets :: ConvexHull -> [(Family, [IndexMap [Double]], [EdgeMap])]
- groupedFacets' :: ConvexHull -> [(Family, IndexMap [Double], EdgeMap)]
- facetToPolygon :: Facet -> ([(Index, [Double])], Bool)
- facetToPolygon' :: Facet -> [(Index, [Double])]
- ridgeToPolygon :: Ridge -> [(Index, [Double])]
- hullToSTL :: ConvexHull -> FilePath -> IO ()
Documentation
class HasVertices m where Source #
Instances
verticesIds :: HasVertices a => a -> [Index] Source #
vertices ids
verticesCoordinates :: HasVertices a => a -> [[Double]] Source #
vertices coordinates
nVertices :: HasVertices a => a -> Int Source #
number of vertices
isEdge :: HasEdges a => a -> (Index, Index) -> Bool Source #
whether a pair of vertices indices form an edge; the order of the indices has no importance
toPoints :: HasEdges a => a -> (Index, Index) -> Maybe ([Double], [Double]) Source #
edge as pair of points; the order of the vertices has no importance
toPoints' :: HasEdges a => a -> (Index, Index) -> ([Double], [Double]) Source #
edge as pair of points, without checking the edge exists
data ConvexHull Source #
ConvexHull | |
|
Instances
Show ConvexHull Source # | |
Defined in Geometry.ConvexHull.Types showsPrec :: Int -> ConvexHull -> ShowS # show :: ConvexHull -> String # showList :: [ConvexHull] -> ShowS # | |
HasEdges ConvexHull Source # | |
Defined in Geometry.ConvexHull.Types _edges :: ConvexHull -> EdgeMap Source # | |
HasVertices ConvexHull Source # | |
Defined in Geometry.ConvexHull.Types |
Vertex | |
|
hullSummary :: ConvexHull -> String Source #
convex hull summary
hullVolume :: ConvexHull -> Double Source #
volume of the convex hull (area in dimension 2, volume in dimension 3, hypervolume in higher dimension)
facetRidges :: ConvexHull -> Facet -> IntMap Ridge Source #
ridges of a facet
facetsVerticesIds :: ConvexHull -> [[Index]] Source #
vertices ids of all facets
ridgesVerticesIds :: ConvexHull -> [[Index]] Source #
vertices ids of all ridges
groupedFacets :: ConvexHull -> [(Family, [IndexMap [Double]], [EdgeMap])] Source #
group facets of the same family
groupedFacets' :: ConvexHull -> [(Family, IndexMap [Double], EdgeMap)] Source #
group facets of the same family and merge vertices and edges
facetToPolygon :: Facet -> ([(Index, [Double])], Bool) Source #
for 3D only, orders the vertices of the facet (i.e. provides a polygon); also returns a Boolean indicating the orientation of the vertices
facetToPolygon' :: Facet -> [(Index, [Double])] Source #
for 3D only, orders the vertices of the facet (i.e. provides a polygon) in anticlockwise orientation