directed-cubical-0.1.0.0: Finite Directed Cubical Complexes and associated algorithms

Portabilityportable
Stabilityexperimental
Maintainerm.misamore@gmail.com
Safe HaskellNone

Math.Topology.CubeCmplx.DirCubeCmplx

Contents

Description

Finite directed cubical complexes and associated algorithms for creating and transforming them.

Synopsis

Vertices

type T = Int8Source

A generic notation for coordinate values.

data Vertex Source

A vertex with lexicographic ordering.

vertex :: [T] -> Maybe VertexSource

Safe constructor for vertices.

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.

vertexPtWise :: (T -> T -> T) -> Vertex -> Vertex -> VertexSource

vAdd :: Vertex -> Vertex -> VertexSource

Add two vertices coordinate-wise.

vSub :: Vertex -> Vertex -> VertexSource

Subtract two vertices coordinate-wise.

vSubUnsafe :: Vertex -> Vertex -> VertexSource

Subtract two vertices coordinate-wise without bounds checking.

vMin :: Vertex -> Vertex -> VertexSource

Coordinate-wise minimum.

vMax :: Vertex -> Vertex -> VertexSource

Coordinate-wise maximum.

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.

vDim :: Vertex -> IntSource

Fetch ambient dimension of a vertex.

Vertex spans

data VertSpan Source

A cubical vertex span.

vertSpan :: Vertex -> Vertex -> Maybe VertSpanSource

Safe constructor for vertex spans. Sanity checks for matching ambient coordinate systems.

vsUnsafe :: Vertex -> Vertex -> VertSpanSource

Unsafe constructor for vertex spans.

vsVert :: Vertex -> VertSpanSource

View a vertex as a 0-dimensional vertex span.

vsFstList :: VertSpan -> [T]Source

Get coordinates for lower vertex in coordinate span.

vsSndList :: VertSpan -> [T]Source

Get coordinates for upper vertex in coordinate span.

vsCoords :: [T] -> [T] -> Maybe VertSpanSource

Safe constructor for vertex spans from coordinates.

vsCoordsUnsafe :: [T] -> [T] -> VertSpanSource

Unsafe constructor for vertex spans from coordinates.

vsDim :: VertSpan -> IntSource

Given a vertex span, determine the corresponding cubical dimension.

vsIsCell :: VertSpan -> BoolSource

Test whether a vertex span is a cubical cell.

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

data CubeCell Source

A cubical cell.

Instances

Eq CubeCell 
Ord CubeCell

Lexicographically ordered by endpoints.

Show CubeCell

Show endpoints.

Arbitrary CubeCell

Random cubical cells.

NFData CubeCell 
Hashable CubeCell

For storing cubical cells in unordered containers.

minVert :: CubeCell -> VertexSource

Get the minimum vertex for a cubical cell.

maxVert :: CubeCell -> VertexSource

Get the maximum vertex for a cubical cell.

cell :: [T] -> [T] -> Maybe CubeCellSource

Safe constructor for cubical cells from coordinates.

cellUnsafe :: [T] -> [T] -> CubeCellSource

Unsafe constructor for cubical cells from coordinates.

cellDim :: CubeCell -> IntSource

Get dimension of a cell.

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.

vInSpan :: Vertex -> VertSpan -> BoolSource

Test whether a vertex belongs to a given vertex span.

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

nCubes :: [CubeCell]Source

List of all possible generic n-cubes, presented as cells (memoized).

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).

nCubeBdry :: Int -> [CubeCell]Source

List of cells in boundary of a generic n-cube (memoized).

nCubeKSkels :: Int -> Int -> [CubeCell]Source

List top-cells in k-skeleta of generic n-cube (memoized).

verts :: CubeCell -> [Vertex]Source

Given a (nongeneric) cubical cell, list its vertices.

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

data CubeCmplx Source

A cubical complex consists of a set of top-cells.

Instances

Eq CubeCmplx 
Show CubeCmplx 
Arbitrary CubeCmplx

A random cubical complex will be a vertex span with a random subset of top-cells removed. Not ideal since every cell will have the same dimension.

NFData CubeCmplx 

cmplxEmpty :: CubeCmplxSource

An empty complex.

cmplxNull :: CubeCmplx -> BoolSource

Detect if complex is empty.

cmplxSize :: CubeCmplx -> IntSource

Get the size of a cubical 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.

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 list of cells to delete from a complex, delete them if present.

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.

Utilities

lazyProd :: [[a]] -> [[a]]Source

Space-efficient cartesian product of list of finite domains