Safe Haskell | None |
---|---|
Language | Haskell98 |
A module defining a type for hypergraphs.
- data Hypergraph a = H [a] [[a]]
- hypergraph :: Ord a => [a] -> [[a]] -> Hypergraph a
- toHypergraph :: Ord a => [a] -> [[a]] -> Hypergraph a
- isUniform :: Ord a => Hypergraph a -> Bool
- same :: Eq a => [a] -> Bool
- fromGraph :: Graph a -> Hypergraph a
- fromDesign :: Ord a => Design a -> Hypergraph a
- incidenceGraph :: Ord a => Hypergraph a -> Graph (Either a [a])
- incidenceMatrix :: (Num t, Eq a) => Hypergraph a -> [[t]]
- fromIncidenceMatrix :: (Ord a1, Num a1, Num a, Eq a, Enum a1) => [[a]] -> Hypergraph a1
- isPartialLinearSpace :: Ord a => Hypergraph a -> Bool
- isProjectivePlane :: Ord a => Hypergraph a -> Bool
- isProjectivePlaneTri :: Ord a => Hypergraph a -> Bool
- isProjectivePlaneQuad :: Ord a => Hypergraph a -> Bool
- isGeneralizedQuadrangle :: Ord a => Hypergraph a -> Bool
- grid :: (Ord t1, Ord t, Num t1, Num t, Enum t1, Enum t) => t -> t1 -> Hypergraph (t, t1)
- dualGrid :: Integral a => a -> a -> Hypergraph a
- isGenQuadrangle' :: Ord a => Hypergraph a -> Bool
- isConfiguration :: Ord a => Hypergraph a -> Bool
- fanoPlane :: Hypergraph Integer
- heawoodGraph :: Graph (Either Integer [Integer])
- desarguesConfiguration :: Hypergraph [Integer]
- desarguesGraph :: Graph (Either [Integer] [[Integer]])
- pappusConfiguration :: Hypergraph Integer
- pappusGraph :: Graph (Either Integer [Integer])
- coxeterGraph :: Graph [Integer]
- duads :: [[Integer]]
- synthemes :: [[[Integer]]]
- tutteCoxeterGraph :: Graph (Either [Integer] [[Integer]])
- intersectionGraph :: Ord a => Hypergraph a -> Graph [a]
Documentation
data Hypergraph a Source
H [a] [[a]] |
Eq a => Eq (Hypergraph a) | |
Ord a => Ord (Hypergraph a) | |
Show a => Show (Hypergraph a) |
hypergraph :: Ord a => [a] -> [[a]] -> Hypergraph a Source
toHypergraph :: Ord a => [a] -> [[a]] -> Hypergraph a Source
isUniform :: Ord a => Hypergraph a -> Bool Source
Is this hypergraph uniform - meaning that all blocks are of the same size
fromGraph :: Graph a -> Hypergraph a Source
fromDesign :: Ord a => Design a -> Hypergraph a Source
incidenceGraph :: Ord a => Hypergraph a -> Graph (Either a [a]) Source
incidenceMatrix :: (Num t, Eq a) => Hypergraph a -> [[t]] Source
fromIncidenceMatrix :: (Ord a1, Num a1, Num a, Eq a, Enum a1) => [[a]] -> Hypergraph a1 Source
isPartialLinearSpace :: Ord a => Hypergraph a -> Bool Source
isProjectivePlane :: Ord a => Hypergraph a -> Bool Source
Is this hypergraph a projective plane - meaning that any two lines meet in a unique point, and any two points lie on a unique line
isProjectivePlaneTri :: Ord a => Hypergraph a -> Bool Source
Is this hypergraph a projective plane with a triangle. This is a weak non-degeneracy condition, which eliminates all points on the same line, or all lines through the same point.
isProjectivePlaneQuad :: Ord a => Hypergraph a -> Bool Source
Is this hypergraph a projective plane with a quadrangle. This is a stronger non-degeneracy condition.
isGeneralizedQuadrangle :: Ord a => Hypergraph a -> Bool Source
dualGrid :: Integral a => a -> a -> Hypergraph a Source
isGenQuadrangle' :: Ord a => Hypergraph a -> Bool Source
isConfiguration :: Ord a => Hypergraph a -> Bool Source
Is this hypergraph a (projective) configuration.
heawoodGraph :: Graph (Either Integer [Integer]) Source
The Heawood graph is the incidence graph of the Fano plane
coxeterGraph :: Graph [Integer] Source
tutteCoxeterGraph :: Graph (Either [Integer] [[Integer]]) Source
The Tutte-Coxeter graph, also called the Tutte 8-cage
intersectionGraph :: Ord a => Hypergraph a -> Graph [a] Source