Safe Haskell | None |
---|---|
Language | Haskell98 |
A module defining a type for hypergraphs.
Synopsis
- 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 :: (Eq a1, Num a2) => Hypergraph a1 -> [[a2]]
- fromIncidenceMatrix :: (Num a1, Enum a1, Ord a1, Num a2, Eq a2) => [[a2]] -> 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 a, Ord b, Num a, Num b, Enum a, Enum b) => a -> b -> Hypergraph (a, b)
- 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]] |
Instances
Eq a => Eq (Hypergraph a) Source # | |
Defined in Math.Combinatorics.Hypergraph (==) :: Hypergraph a -> Hypergraph a -> Bool # (/=) :: Hypergraph a -> Hypergraph a -> Bool # | |
Ord a => Ord (Hypergraph a) Source # | |
Defined in Math.Combinatorics.Hypergraph compare :: Hypergraph a -> Hypergraph a -> Ordering # (<) :: Hypergraph a -> Hypergraph a -> Bool # (<=) :: Hypergraph a -> Hypergraph a -> Bool # (>) :: Hypergraph a -> Hypergraph a -> Bool # (>=) :: Hypergraph a -> Hypergraph a -> Bool # max :: Hypergraph a -> Hypergraph a -> Hypergraph a # min :: Hypergraph a -> Hypergraph a -> Hypergraph a # | |
Show a => Show (Hypergraph a) Source # | |
Defined in Math.Combinatorics.Hypergraph showsPrec :: Int -> Hypergraph a -> ShowS # show :: Hypergraph a -> String # showList :: [Hypergraph a] -> ShowS # |
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 :: (Eq a1, Num a2) => Hypergraph a1 -> [[a2]] Source #
fromIncidenceMatrix :: (Num a1, Enum a1, Ord a1, Num a2, Eq a2) => [[a2]] -> 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 #