| Copyright | (c) Stéphane Laurent 2023 |
|---|---|
| License | GPL-3 |
| Maintainer | laurent_step@outlook.fr |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Geometry.Delaunay
Description
See README for an example.
Synopsis
- type Index = Int
- type IndexMap = IntMap
- type IndexSet = IntSet
- data IndexPair = Pair Index Index
- type EdgeMap = InsOrdHashMap IndexPair ([Double], [Double])
- data Family
- class HasCenter m where
- class HasEdges m where
- class HasFamily m where
- class HasNormal m where
- class HasVertices m where
- class HasVolume m where
- sameFamily :: Family -> Family -> Bool
- 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 Site = Site {}
- data Simplex = Simplex {
- _vertices' :: IndexMap [Double]
- _circumcenter :: [Double]
- _circumradius :: Double
- _volume' :: Double
- data TileFacet = TileFacet {}
- data Tile = Tile {
- _simplex :: Simplex
- _neighborsIds :: IntSet
- _facetsIds :: IntSet
- _family' :: Family
- _toporiented :: Bool
- data Tessellation = Tessellation {}
- delaunay :: [[Double]] -> Bool -> Bool -> Maybe Double -> IO Tessellation
- vertexNeighborFacets :: Tessellation -> Index -> IntMap TileFacet
- sandwichedFacet :: TileFacet -> Bool
- facetOf :: Tessellation -> TileFacet -> IntMap Tile
- facetFamilies :: Tessellation -> TileFacet -> IntMap Family
- facetCenters :: Tessellation -> TileFacet -> IntMap [Double]
- facetOf' :: Tessellation -> Int -> IntMap Tile
- facetFamilies' :: Tessellation -> Int -> IntMap Family
- facetCenters' :: Tessellation -> Int -> IntMap [Double]
- getDelaunayTiles :: Tessellation -> [IntMap [Double]]
Documentation
class HasEdges m where Source #
Instances
| HasEdges Tessellation Source # | |
Defined in Geometry.Delaunay.Types Methods _edges :: Tessellation -> EdgeMap Source # | |
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
Constructors
| Site | |
Fields
| |
Constructors
| Simplex | |
Fields
| |
Constructors
| TileFacet | |
Constructors
| Tile | |
Fields
| |
data Tessellation Source #
Constructors
| Tessellation | |
Instances
| Show Tessellation Source # | |
Defined in Geometry.Delaunay.Types Methods showsPrec :: Int -> Tessellation -> ShowS # show :: Tessellation -> String # showList :: [Tessellation] -> ShowS # | |
| HasEdges Tessellation Source # | |
Defined in Geometry.Delaunay.Types Methods _edges :: Tessellation -> EdgeMap Source # | |
| HasVertices Tessellation Source # | |
Defined in Geometry.Delaunay.Types | |
| HasVolume Tessellation Source # | |
Defined in Geometry.Delaunay.Types Methods _volume :: Tessellation -> Double Source # | |
vertexNeighborFacets :: Tessellation -> Index -> IntMap TileFacet Source #
tile facets a vertex belongs to, vertex given by its index; the output is the empty map if the index is not valid
sandwichedFacet :: TileFacet -> Bool Source #
whether a tile facet is sandwiched between two tiles
facetFamilies :: Tessellation -> TileFacet -> IntMap Family Source #
the families of the tiles a facet belongs to
facetCenters :: Tessellation -> TileFacet -> IntMap [Double] Source #
the circumcenters of the tiles a facet belongs to
facetOf' :: Tessellation -> Int -> IntMap Tile Source #
the tiles a facet belongs to, facet given by its id
facetFamilies' :: Tessellation -> Int -> IntMap Family Source #
the families of the tiles a facet belongs to, facet given by its id
facetCenters' :: Tessellation -> Int -> IntMap [Double] Source #
the circumcenters of the tiles a facet belongs to, facet given by its id
getDelaunayTiles :: Tessellation -> [IntMap [Double]] Source #
list of the maps of vertices for all tiles