module Math.Combinatorics.Graph where
import qualified Data.List as L
import Data.Maybe (isJust)
import qualified Data.Map as M
import qualified Data.Set as S
import Control.Arrow ( (&&&) )
import Math.Common.ListSet as LS
import Math.Core.Utils
import Math.Algebra.Group.PermutationGroup hiding (fromDigits, fromBinary)
import qualified Math.Algebra.Group.SchreierSims as SS
set xs = map head $ L.group $ L.sort xs
powerset [] = [[]]
powerset (x:xs) = let p = powerset xs in p ++ map (x:) p
data Graph a = G [a] [[a]] deriving (Eq,Ord,Show)
instance Functor Graph where
fmap f (G vs es) = G (map f vs) (map (map f) es)
nf :: Ord a => Graph a -> Graph a
nf (G vs es) = G vs' es' where
vs' = L.sort vs
es' = L.sort (map L.sort es)
isSetSystem xs bs = isListSet xs && isListSet bs && all isListSet bs && all (`isSubset` xs) bs
isGraph vs es = isSetSystem vs es && all ( (==2) . length) es
graph :: (Ord t) => ([t], [[t]]) -> Graph t
graph (vs,es) | isGraph vs es = G vs es
toGraph (vs,es) | isGraph vs' es' = G vs' es' where
vs' = L.sort vs
es' = L.sort $ map L.sort es
vertices (G vs _) = vs
edges (G _ es) = es
incidenceMatrix (G vs es) = [ [if v `elem` e then 1 else 0 | v <- vs] | e <- es]
fromIncidenceMatrix m = graph (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]
adjacencyMatrix (G vs es) =
[ [if L.sort [i,j] `S.member` es' then 1 else 0 | j <- vs] | i <- vs]
where es' = S.fromList es
fromAdjacencyMatrix m = graph (vs,es) where
n = L.genericLength m
vs = [1..n]
es = es' 1 m
es' i (r:rs) = [ [i,j] | (j,1) <- drop i (zip vs r)] ++ es' (i+1) rs
es' _ [] = []
nullGraph :: (Integral t) => t -> Graph t
nullGraph n = G [1..n] []
nullGraph' :: Graph Int
nullGraph' = G [] []
c :: (Integral t) => t -> Graph t
c n | n >= 3 = graph (vs,es) where
vs = [1..n]
es = L.insert [1,n] [[i,i+1] | i <- [1..n-1]]
k :: (Integral t) => t -> Graph t
k n = graph (vs,es) where
vs = [1..n]
es = [[i,j] | i <- [1..n-1], j <- [i+1..n]]
kb :: (Integral t) => t -> t -> Graph t
kb m n = to1n $ kb' m n
kb' :: (Integral t) => t -> t -> Graph (Either t t)
kb' m n = graph (vs,es) where
vs = map Left [1..m] ++ map Right [1..n]
es = [ [Left i, Right j] | i <- [1..m], j <- [1..n] ]
q :: (Integral t) => Int -> Graph t
q k = fromBinary $ q' k
q' :: (Integral t) => Int -> Graph [t]
q' k = graph (vs,es) where
vs = sequence $ replicate k [0,1]
es = [ [u,v] | [u,v] <- combinationsOf 2 vs, hammingDistance u v == 1 ]
hammingDistance as bs = length $ filter id $ zipWith (/=) as bs
tetrahedron = k 4
cube = q 3
octahedron = graph (vs,es) where
vs = [1..6]
es = combinationsOf 2 vs L.\\ [[1,6],[2,5],[3,4]]
dodecahedron = toGraph (vs,es) where
vs = [1..20]
es = [ [1,2],[2,3],[3,4],[4,5],[5,1],
[6,7],[7,8],[8,9],[9,10],[10,11],[11,12],[12,13],[13,14],[14,15],[15,6],
[16,17],[17,18],[18,19],[19,20],[20,16],
[1,6],[2,8],[3,10],[4,12],[5,14],
[7,16],[9,17],[11,18],[13,19],[15,20] ]
icosahedron = toGraph (vs,es) where
vs = [1..12]
es = [ [1,2],[1,3],[1,4],[1,5],[1,6],
[2,3],[3,4],[4,5],[5,6],[6,2],
[7,12],[8,12],[9,12],[10,12],[11,12],
[7,8],[8,9],[9,10],[10,11],[11,7],
[2,7],[7,3],[3,8],[8,4],[4,9],[9,5],[5,10],[10,6],[6,11],[11,2] ]
prism :: Int -> Graph (Int,Int)
prism n = k 2 `cartProd` c n
to1n (G vs es) = graph (vs',es') where
mapping = M.fromList $ zip vs [1..]
vs' = M.elems mapping
es' = [map (mapping M.!) e | e <- es]
fromDigits :: Integral a => Graph [a] -> Graph a
fromDigits = fmap fromDigits'
fromBinary :: Integral a => Graph [a] -> Graph a
fromBinary = fmap fromBinary'
petersen :: Graph [Integer]
petersen = graph (vs,es) where
vs = combinationsOf 2 [1..5]
es = [ [v1,v2] | [v1,v2] <- combinationsOf 2 vs, disjoint v1 v2]
complement :: (Ord t) => Graph t -> Graph t
complement (G vs es) = graph (vs,es') where es' = combinationsOf 2 vs LS.\\ es
restriction :: (Eq a) => Graph a -> [a] -> Graph a
restriction g@(G vs es) us = G us (es `restrict` us)
where es `restrict` us = [e | e@[i,j] <- es, i `elem` us, j `elem` us]
inducedSubgraph :: (Eq a) => Graph a -> [a] -> Graph a
inducedSubgraph g@(G vs es) us = G us (es `restrict` us)
where es `restrict` us = [e | e@[i,j] <- es, i `elem` us, j `elem` us]
lineGraph g = to1n $ lineGraph' g
lineGraph' (G vs es) = graph (es, [ [ei,ej] | ei <- es, ej <- dropWhile (<= ei) es, ei `intersect` ej /= [] ])
cartProd (G vs es) (G vs' es') = G us [e | e@[u,u'] <- combinationsOf 2 us, u `adj` u' ]
where us = [(v,v') | v <- vs, v' <- vs']
eset = S.fromList es
eset' = S.fromList es'
adj (x1,y1) (x2,y2) = x1 == x2 && L.sort [y1,y2] `S.member` eset'
|| y1 == y2 && L.sort [x1,x2] `S.member` eset
order = length . vertices
size = length . edges
valency (G vs es) v = length $ filter (v `elem`) es
valencies g@(G vs es) = map (head &&& length) $ L.group $ L.sort $ map (valency g) vs
valencyPartition g@(G vs es) = map (map snd) $ L.groupBy (\x y -> fst x == fst y) [(valency g v, v) | v <- vs]
regularParam g =
case valencies g of
[(v,_)] -> Just v
_ -> Nothing
isRegular :: (Eq t) => Graph t -> Bool
isRegular g = isJust $ regularParam g
isCubic :: (Eq t) => Graph t -> Bool
isCubic g = regularParam g == Just 3
nbrs (G vs es) v = [u | [u,v'] <- es, v == v']
++ [w | [v',w] <- es, v == v']
findPaths g@(G vs es) x y = map reverse $ bfs [ [x] ] where
bfs ((z:zs) : nodes)
| z == y = (z:zs) : bfs nodes
| otherwise = bfs (nodes ++ [(w:z:zs) | w <- nbrs g z, w `notElem` zs])
bfs [] = []
distance :: (Eq a) => Graph a -> a -> a -> Int
distance g x y =
case findPaths g x y of
[] -> -1
p:ps -> length p - 1
diameter :: (Ord t) => Graph t -> Int
diameter g@(G vs es)
| isConnected g = maximum $ map maxDistance vs
| otherwise = -1
where maxDistance v = length (distancePartition g v) - 1
findCycles g@(G vs es) x = [reverse (x:z:zs) | z:zs <- bfs [ [x] ], z `elem` nbrsx, length zs > 1] where
nbrsx = nbrs g x
bfs ((z:zs) : nodes) = (z:zs) : bfs (nodes ++ [ w:z:zs | w <- nbrs g z, w `notElem` zs])
bfs [] = []
girth :: (Eq t) => Graph t -> Int
girth g@(G vs es) = minimum' $ map minCycle vs where
minimum' xs = let (zs,nzs) = L.partition (==0) xs in if null nzs then -1 else minimum nzs
minCycle v = case findCycles g v of
[] -> 0
c:cs -> length c - 1
distancePartition g@(G vs es) v = distancePartitionS vs (S.fromList es) v
distancePartitionS vs eset v = distancePartition' (S.singleton v) (S.delete v (S.fromList vs)) where
distancePartition' boundary exterior
| S.null boundary = if S.null exterior then [] else [S.toList exterior]
| otherwise = let (boundary', exterior') = S.partition (\v -> any (`S.member` eset) [L.sort [u,v] | u <- S.toList boundary]) exterior
in S.toList boundary : distancePartition' boundary' exterior'
component g v = component' S.empty (S.singleton v) where
component' interior boundary
| S.null boundary = S.toList interior
| otherwise = let interior' = S.union interior boundary
boundary' = foldl S.union S.empty [S.fromList (nbrs g x) | x <- S.toList boundary] S.\\ interior'
in component' interior' boundary'
isConnected :: (Ord t) => Graph t -> Bool
isConnected g@(G (v:vs) es) = length (component g v) == length (v:vs)
isConnected (G [] []) = True
components g = components' (vertices g)
where components' [] = []
components' (v:vs) = let c = component g v in c : components' (vs LS.\\ c)
j v k i | v >= k && k >= i
= graph (vs,es) where
vs = combinationsOf k [1..v]
es = [ [v1,v2] | [v1,v2] <- combinationsOf 2 vs, length (v1 `intersect` v2) == i ]
kneser :: Int -> Int -> Graph [Int]
kneser n k | 2*k <= n = graph (vs,es) where
vs = combinationsOf k [1..n]
es = [ [v1,v2] | [v1,v2] <- combinationsOf 2 vs, disjoint v1 v2]
johnson v k | v >= 2*k = j v k (k-1)
bipartiteKneser n k | 2*k < n = graph (vs,es) where
vs = map Left (combinationsOf k [1..n])
++ map Right (combinationsOf (n-k) [1..n])
es = [ [Left u, Right v] | u <- combinationsOf k [1..n], v <- combinationsOf (n-k) [1..n], u `isSubset` v]
desargues1 = bipartiteKneser 5 2
gp n k | 2*k < n = toGraph (vs,es) where
vs = map Left [0..n-1] ++ map Right [0..n-1]
es = (map . map) Left [ [i, (i+1) `mod` n] | i <- [0..n-1] ]
++ [ [Left i, Right i] | i <- [0..n-1] ]
++ (map . map) Right [ [i, (i+k) `mod` n] | i <- [0..n-1] ]
petersen2 = gp 5 2
prism' n = gp n 1
durer = gp 6 2
mobiusKantor = gp 8 3
dodecahedron2 = gp 10 2
desargues2 = gp 10 3