module Math.Combinatorics.Hypergraph where
import qualified Data.List as L
import Math.Common.ListSet
import Math.Core.Utils (combinationsOf)
import Math.Combinatorics.Graph hiding (incidenceMatrix)
import Math.Algebra.Group.PermutationGroup (orbitB, p)
import Math.Algebra.Field.Base
import Math.Algebra.Field.Extension
import Math.Combinatorics.Design hiding (incidenceMatrix, incidenceGraph, dual, isSubset, fanoPlane)
data Hypergraph a = H [a] [[a]] deriving (Eq,Ord,Show)
hypergraph xs bs | isSetSystem xs bs = H xs bs
toHypergraph xs bs = H xs' bs' where
xs' = L.sort xs
bs' = L.sort $ map L.sort bs
isUniform :: (Ord a) => Hypergraph a -> Bool
isUniform h@(H xs bs) = isSetSystem xs bs && same (map length bs)
same (x:xs) = all (==x) xs
same [] = True
fromGraph (G vs es) = H vs es
fromDesign (D xs bs) = H xs (L.sort bs)
incidenceGraph :: (Ord a) => Hypergraph a -> Graph (Either a [a])
incidenceGraph (H xs bs) = G vs es where
vs = map Left xs ++ map Right bs
es = L.sort [ [Left x, Right b] | b <- bs, x <- b]
incidenceMatrix (H vs es) = [ [if v `elem` e then 1 else 0 | v <- vs] | e <- es]
fromIncidenceMatrix m = H vs es where
n = L.genericLength $ head m
vs = [1..n]
es = L.sort $ map edge m
edge row = [v | (1,v) <- zip row vs]
isPartialLinearSpace :: (Ord a) => Hypergraph a -> Bool
isPartialLinearSpace h@(H ps ls) =
isSetSystem ps ls &&
all ( (<=1) . length ) [filter (pair `isSubset`) ls | pair <- combinationsOf 2 ps]
isProjectivePlane :: (Ord a) => Hypergraph a -> Bool
isProjectivePlane h@(H ps ls) =
isSetSystem ps ls &&
all ( (==1) . length) [intersect l1 l2 | [l1,l2] <- combinationsOf 2 ls] &&
all ( (==1) . length) [ filter ([p1,p2] `isSubset`) ls | [p1,p2] <- combinationsOf 2 ps]
isProjectivePlaneTri :: (Ord a) => Hypergraph a -> Bool
isProjectivePlaneTri h@(H ps ls) =
isProjectivePlane h && any triangle (combinationsOf 3 ps)
where triangle t@[p1,p2,p3] =
(not . null) [l | l <- ls, [p1,p2] `isSubset` l, p3 `notElem` l] &&
(not . null) [l | l <- ls, [p1,p3] `isSubset` l, p2 `notElem` l] &&
(not . null) [l | l <- ls, [p2,p3] `isSubset` l, p1 `notElem` l]
isProjectivePlaneQuad :: (Ord a) => Hypergraph a -> Bool
isProjectivePlaneQuad h@(H ps ls) =
isProjectivePlane h && any quadrangle (combinationsOf 4 ps)
where quadrangle q = all (not . collinear) (combinationsOf 3 q)
collinear ps = any (ps `isSubset`) ls
isGeneralizedQuadrangle :: (Ord a) => Hypergraph a -> Bool
isGeneralizedQuadrangle h@(H ps ls) =
isPartialLinearSpace h &&
all (\(l,p) -> unique [p' | p' <- l, collinear (pair p p')]) [(l,p) | l <- ls, p <- ps, p `notElem` l] &&
any (not . collinear) (powerset ps) &&
any (not . concurrent) (powerset ls)
where unique xs = length xs == 1
pair x y = if x < y then [x,y] else [y,x]
collinear ps = any (ps `isSubset`) ls
concurrent ls = any (\p -> all (p `elem`) ls) ps
grid m n = H ps ls where
ps = [(i,j) | i <- [1..m], j <- [1..n] ]
ls = L.sort $ [ [(i,j) | i <- [1..m] ] | j <- [1..n] ]
++ [ [(i,j) | j <- [1..n] ] | i <- [1..m] ]
dualGrid m n = fromGraph $ kb m n
isGenQuadrangle' h = diameter g == 4 && girth g == 8
where g = incidenceGraph h
isConfiguration :: (Ord a) => Hypergraph a -> Bool
isConfiguration h@(H ps ls) =
isUniform h &&
same [length (filter (p `elem`) ls) | p <- ps]
fanoPlane :: Hypergraph Integer
fanoPlane = toHypergraph [1..7] [[1,2,4],[2,3,5],[3,4,6],[4,5,7],[5,6,1],[6,7,2],[7,1,3]]
heawoodGraph :: Graph (Either Integer [Integer])
heawoodGraph = incidenceGraph fanoPlane
desarguesConfiguration :: Hypergraph [Integer]
desarguesConfiguration = H xs bs where
xs = combinationsOf 2 [1..5]
bs = [ [x | x <- xs, x `isSubset` b] | b <- combinationsOf 3 [1..5] ]
desarguesGraph :: Graph (Either [Integer] [[Integer]])
desarguesGraph = incidenceGraph desarguesConfiguration
pappusConfiguration :: Hypergraph Integer
pappusConfiguration = H xs bs where
xs = [1..9]
bs = L.sort [ [1,2,3], [4,5,6], [7,8,9], [1,5,9], [1,6,8], [2,4,9], [3,4,8], [2,6,7], [3,5,7] ]
pappusGraph :: Graph (Either Integer [Integer])
pappusGraph = incidenceGraph pappusConfiguration
coxeterGraph :: Graph [Integer]
coxeterGraph = G vs es where
g = p [[1..7]]
vs = L.sort $ concatMap (orbitB [g]) [[1,2,4],[3,5,7],[3,6,7],[5,6,7]]
es = [ e | e@[v1,v2] <- combinationsOf 2 vs, disjoint v1 v2]
duads = combinationsOf 2 [1..6]
synthemes = [ [d1,d2,d3] | d1 <- duads,
d2 <- duads, d2 > d1, disjoint d1 d2,
d3 <- duads, d3 > d2, disjoint d1 d3, disjoint d2 d3 ]
tutteCoxeterGraph :: Graph (Either [Integer] [[Integer]])
tutteCoxeterGraph = incidenceGraph $ H duads synthemes
intersectionGraph (H xs bs) = G vs es where
vs = bs
es = [pair | pair@[b1,b2] <- combinationsOf 2 bs, not (disjoint b1 b2)]