Portability | portable |
---|---|
Stability | experimental |
Maintainer | m.misamore@gmail.com |
Safe Haskell | None |
Finite directed cubical complexes and associated algorithms for creating and transforming them.
- type T = Int8
- data Vertex
- vertex :: [T] -> Maybe Vertex
- coords :: Vertex -> Vector T
- vertexUnsafe :: [T] -> Vertex
- vertexVectorUnsafe :: Vector T -> Vertex
- vertexToList :: Vertex -> [T]
- vertexPtWise :: (T -> T -> T) -> Vertex -> Vertex -> Vertex
- vAdd :: Vertex -> Vertex -> Vertex
- vSub :: Vertex -> Vertex -> Vertex
- vSubUnsafe :: Vertex -> Vertex -> Vertex
- vMin :: Vertex -> Vertex -> Vertex
- vMax :: Vertex -> Vertex -> Vertex
- vGT :: Vertex -> Vertex -> Bool
- vLT :: Vertex -> Vertex -> Bool
- vDim :: Vertex -> Int
- data VertSpan
- vertSpan :: Vertex -> Vertex -> Maybe VertSpan
- vsFst :: VertSpan -> Vertex
- vsSnd :: VertSpan -> Vertex
- vsUnsafe :: Vertex -> Vertex -> VertSpan
- vsVert :: Vertex -> VertSpan
- vsFstList :: VertSpan -> [T]
- vsSndList :: VertSpan -> [T]
- vsCoords :: [T] -> [T] -> Maybe VertSpan
- vsCoordsUnsafe :: [T] -> [T] -> VertSpan
- vsDim :: VertSpan -> Int
- vsIsCell :: VertSpan -> Bool
- vsFatten :: VertSpan -> VertSpan
- vsCornerPairs :: VertSpan -> HashSet (CubeCell, Vertex)
- vsCornerVerts :: VertSpan -> HashSet Vertex
- vsBdry :: VertSpan -> [VertSpan]
- data CubeCell
- minVert :: CubeCell -> Vertex
- maxVert :: CubeCell -> Vertex
- cell :: [T] -> [T] -> Maybe CubeCell
- cellUnsafe :: [T] -> [T] -> CubeCell
- cellDim :: CubeCell -> Int
- cellVertsUnsafe :: Vertex -> Vertex -> CubeCell
- cellVerts :: Vertex -> Vertex -> Maybe CubeCell
- spanTopCells :: VertSpan -> [CubeCell]
- vertToCell :: Vertex -> CubeCell
- inSpan :: CubeCell -> VertSpan -> Bool
- isTopCell :: CubeCell -> CubeCmplx -> Bool
- vInSpan :: Vertex -> VertSpan -> Bool
- inBdry :: CubeCell -> VertSpan -> Bool
- spanBdryCells :: VertSpan -> [[CubeCell]]
- nCubes :: [CubeCell]
- nCubeVerts :: Int -> [CubeCell]
- nCubeCells :: Int -> [CubeCell]
- nCubeProperCells :: Int -> [CubeCell]
- nCubeBdry :: Int -> [CubeCell]
- nCubeKSkels :: Int -> Int -> [CubeCell]
- verts :: CubeCell -> [Vertex]
- subCells :: CubeCell -> [CubeCell]
- properSubCells :: CubeCell -> [CubeCell]
- bdry :: CubeCell -> [CubeCell]
- kSkel :: Int -> CubeCell -> [CubeCell]
- isSubCell :: CubeCell -> CubeCell -> Bool
- isPropSubCell :: CubeCell -> CubeCell -> Bool
- opFaceUnsafe :: CubeCell -> CubeCell -> CubeCell
- genToNonGen :: CubeCell -> CubeCell -> CubeCell
- nonGenToGen :: CubeCell -> CubeCell -> CubeCell
- data CubeCmplx
- cells :: CubeCmplx -> HashSet CubeCell
- cmplxEmpty :: CubeCmplx
- cmplxNull :: CubeCmplx -> Bool
- cmplxSize :: CubeCmplx -> Int
- cmplxApply :: CubeCmplx -> (CubeCell -> HashSet CubeCell) -> CubeCmplx
- cmplxVertOp :: CubeCmplx -> Vertex -> (Vertex -> Vertex -> Vertex) -> CubeCmplx
- vsCmplx :: VertSpan -> CubeCmplx
- cmplxDelCell :: CubeCmplx -> CubeCell -> CubeCmplx
- cmplxDelCells :: CubeCmplx -> HashSet CubeCell -> CubeCmplx
- cmplxDelVsInt :: CubeCmplx -> VertSpan -> CubeCmplx
- cmplxAddCells :: CubeCmplx -> HashSet CubeCell -> CubeCmplx
- cmplxUnions :: [CubeCmplx] -> CubeCmplx
- cmplxFilter :: (CubeCell -> Bool) -> CubeCmplx -> CubeCmplx
- cmplxHullUnsafe :: CubeCmplx -> VertSpan
- cmplxFilterSpan :: CubeCmplx -> VertSpan -> CubeCmplx
- cmplxFilterSpans :: CubeCmplx -> [VertSpan] -> [(CubeCmplx, VertSpan)]
- cellNhd :: CubeCmplx -> CubeCell -> CubeCmplx
- swissFlag :: (CubeCmplx, [VertSpan])
- sqPairFwd :: (CubeCmplx, [VertSpan])
- sqPairBack :: (CubeCmplx, [VertSpan])
- torus3d :: (CubeCmplx, [VertSpan])
- genusTwo3d :: (CubeCmplx, [VertSpan])
- lazyProd :: [[a]] -> [[a]]
Vertices
A vertex with lexicographic ordering.
vertexUnsafe :: [T] -> VertexSource
Unsafe constructor for vertices.
vertexVectorUnsafe :: Vector T -> VertexSource
Unsafe constructor for vertices from vectors.
vertexToList :: Vertex -> [T]Source
Fetch coordinates for a vertex.
vSubUnsafe :: Vertex -> Vertex -> VertexSource
Subtract two vertices coordinate-wise without bounds checking.
vGT :: Vertex -> Vertex -> BoolSource
Test whether vertex is greater than another in cubical partial ordering.
vLT :: Vertex -> Vertex -> BoolSource
Test whether vertex is less than another in cubical partial ordering.
Vertex spans
A cubical vertex span.
vertSpan :: Vertex -> Vertex -> Maybe VertSpanSource
Safe constructor for vertex spans. Sanity checks for matching ambient coordinate systems.
vsCoordsUnsafe :: [T] -> [T] -> VertSpanSource
Unsafe constructor for vertex spans from coordinates.
vsFatten :: VertSpan -> VertSpanSource
Given a vertex span, extend it by one more unit in every direction in which it already extends.
vsCornerPairs :: VertSpan -> HashSet (CubeCell, Vertex)Source
Given a vertex span, efficiently determine all pairs of (cell,vertex) where the vertices are corner vertices of the span and the cells are the unique top-cells containing them.
vsCornerVerts :: VertSpan -> HashSet VertexSource
Given a vertex span, efficiently determine its corner vertices.
vsBdry :: VertSpan -> [VertSpan]Source
Given a coordinate span, list all coordinate spans of its boundary.
Cells
A cubical cell.
cellUnsafe :: [T] -> [T] -> CubeCellSource
Unsafe constructor for cubical cells from coordinates.
cellVertsUnsafe :: Vertex -> Vertex -> CubeCellSource
Unsafe constructor for cubical cells from vertices.
cellVerts :: Vertex -> Vertex -> Maybe CubeCellSource
Safe constructor for cubical cells from vertices.
spanTopCells :: VertSpan -> [CubeCell]Source
Given a coordinate span, list its top-dimensional cubical cells.
vertToCell :: Vertex -> CubeCellSource
Treat a vertex as a cell.
inSpan :: CubeCell -> VertSpan -> BoolSource
Test whether a cubical cell belongs to a given vertex span.
isTopCell :: CubeCell -> CubeCmplx -> BoolSource
Test whether a cubical cell would be a top-cell if added to a complex
inBdry :: CubeCell -> VertSpan -> BoolSource
Test if a cubical cell is in the boundary of a cubical coordinate span. See also vsBdry and spanBdryCells
spanBdryCells :: VertSpan -> [[CubeCell]]Source
Given a coordinate span, provide a list of top-cells in each face.
Substructures
nCubeVerts :: Int -> [CubeCell]Source
Vertices of generic n-cube, as subcells (memoized).
nCubeCells :: Int -> [CubeCell]Source
Subcells of a generic n-cube (memoized).
nCubeProperCells :: Int -> [CubeCell]Source
Proper subcells of a generic n-cube (mostly memoized).
nCubeKSkels :: Int -> Int -> [CubeCell]Source
List top-cells in k-skeleta of generic n-cube (memoized).
subCells :: CubeCell -> [CubeCell]Source
Given a (nongeneric) cubical cell, get all cubical subcells.
properSubCells :: CubeCell -> [CubeCell]Source
Given a (nongeneric) cubical cell, get all proper cubical subcells.
bdry :: CubeCell -> [CubeCell]Source
Given a (nongeneric) cubical cell of dim n in ambient dim n, get its boundary.
kSkel :: Int -> CubeCell -> [CubeCell]Source
Given a (nongeneric) cubical cell, get top-cells of its k-skeleton.
isSubCell :: CubeCell -> CubeCell -> BoolSource
Test if the former cubical cell is a subcell of the latter.
isPropSubCell :: CubeCell -> CubeCell -> BoolSource
Test if the former cubical cell is a proper subcell of the latter.
opFaceUnsafe :: CubeCell -> CubeCell -> CubeCellSource
Given a face f in some n-cube, get its opposite face (memoized).
Translation
genToNonGen :: CubeCell -> CubeCell -> CubeCellSource
Given a (nongeneric) cell c and a generic cell g representing a subcell of a generic cell of dimension dim c, return the translation of g into the nongeneric coordinates of c.
nonGenToGen :: CubeCell -> CubeCell -> CubeCellSource
Given a subcell s of a (nongeneric) cell c, express s as a subcell of a generic cell of the same dimension as c.
Directed Cubical Complexes
A cubical complex consists of a set of top-cells.
An empty complex.
cmplxApply :: CubeCmplx -> (CubeCell -> HashSet CubeCell) -> CubeCmplxSource
Given a function producing a set of cubical cells from any cubical cell, apply it to a cubical complex to yield a new complex.
cmplxVertOp :: CubeCmplx -> Vertex -> (Vertex -> Vertex -> Vertex) -> CubeCmplxSource
Given a complex and a vertex of the same ambient dimension, translate every cell of the complex by the vertex via the given operation. Typical operation is to add (1,...,1) to force nonzero coordinates without affecting the topology.
vsCmplx :: VertSpan -> CubeCmplxSource
Basic means of constructing cubical complexes via vertex spans.
cmplxDelCell :: CubeCmplx -> CubeCell -> CubeCmplxSource
Given a single cell to delete from a complex, delete it if present.
cmplxDelCells :: CubeCmplx -> HashSet CubeCell -> CubeCmplxSource
Given a set of cells to delete from a complex, delete them if present.
cmplxDelVsInt :: CubeCmplx -> VertSpan -> CubeCmplxSource
Given a vertex span and a complex, delete all top-cells belonging to the span and replace them with the boundaries of these top-cells that belong to the span's boundary. This punches a hole in the complex.
cmplxAddCells :: CubeCmplx -> HashSet CubeCell -> CubeCmplxSource
Given a set of cells to insert into a complex, insert them all.
cmplxUnions :: [CubeCmplx] -> CubeCmplxSource
Union a list of complexes.
cmplxFilter :: (CubeCell -> Bool) -> CubeCmplx -> CubeCmplxSource
Filter the top-cells of a complex on some predicate.
cmplxHullUnsafe :: CubeCmplx -> VertSpanSource
Given a non-empty complex, determine the minimal vertex span containing it. The resulting span need not have the same dimension as the ambient space.
cmplxFilterSpan :: CubeCmplx -> VertSpan -> CubeCmplxSource
Given a complex cx and a vertex span vs, filter the complex down to the subcomplex of all top-cells of cx contained in vs.
cmplxFilterSpans :: CubeCmplx -> [VertSpan] -> [(CubeCmplx, VertSpan)]Source
Given a complex and a list of vertex spans, determine the list of subcomplexes of top-cells supported on these spans, paired up with the spans so that the original boundaries are known.
cellNhd :: CubeCmplx -> CubeCell -> CubeCmplxSource
Given a cell c in a cubical complex, get a subcomplex that includes all all top-cells that could be adjacent to c (including c). Handy for reducing search problems.
Example complexes
swissFlag :: (CubeCmplx, [VertSpan])Source
Standard example of finite directed cubical complex: two classes of paths expected in path category.
sqPairFwd :: (CubeCmplx, [VertSpan])Source
Standard example: four classes of paths expected in path category.
sqPairBack :: (CubeCmplx, [VertSpan])Source
Standard example: three classes of paths expected in path category.
torus3d :: (CubeCmplx, [VertSpan])Source
Standard example: two classes of paths expected in path category.
genusTwo3d :: (CubeCmplx, [VertSpan])Source
Standard example: four classes of paths expected in path category.