module Math.Combinatorics.StronglyRegularGraph where
import qualified Data.List as L
import Data.Maybe (isJust)
import qualified Data.Map as M
import qualified Data.Set as S
import Math.Common.ListSet
import Math.Core.Utils (combinationsOf)
import Math.Algebra.Group.PermutationGroup hiding (P)
import Math.Algebra.Group.SchreierSims as SS
import Math.Combinatorics.Graph as G hiding (G)
import Math.Combinatorics.GraphAuts
import Math.Combinatorics.Design as D
import Math.Algebra.LinearAlgebra
import Math.Algebra.Field.Base
import Math.Combinatorics.FiniteGeometry
srgParams g
| null es = error "srgParams: not defined for null graph"
| null es' = error "srgParams: not defined for complete graph"
| otherwise =
if all (==k) ks && all (==lambda) ls && all (==mu) ms
then Just (n,k,lambda,mu)
else Nothing
where vs = vertices g
n = length vs
es = edges g
es' = combinationsOf 2 vs \\ es
k:ks = map (valency g) vs
lambda:ls = map (length . commonNbrs) es
mu:ms = map (length . commonNbrs) es'
commonNbrs [v1,v2] = (nbrs_g M.! v1) `intersect` (nbrs_g M.! v2)
nbrs_g = M.fromList [ (v, nbrs g v) | v <- vs ]
isSRG g = isJust $ srgParams g
t' m = G.to1n $ t m
t m | m >= 4 = graph (vs,es) where
vs = combinationsOf 2 [1..m]
es = [ [v,v'] | v <- vs, v' <- dropWhile (<= v) vs, not (disjoint v v')]
l2' m = G.to1n $ l2 m
l2 m | m >= 2 = graph (vs,es) where
vs = [ (i,j) | i <- [1..m], j <- [1..m] ]
es = [ [v,v'] | v@(i,j) <- vs, v'@(i',j') <- dropWhile (<= v) vs, i == i' || j == j']
paleyGraph fq | length fq `mod` 4 == 1 = graph (vs,es) where
vs = fq
qs = set [x^2 | x <- vs] \\ [0]
es = [ [x,y] | x <- vs, y <- vs, x < y, (xy) `elem` qs]
clebsch' = G.to1n clebsch
clebsch = graph (vs,es) where
vs = L.sort $ filter (even . length) $ powerset [1..5]
es = [ [v,v'] | v <- vs, v' <- dropWhile (<= v) vs, length (symDiff v v') == 4]
clebsch2 = graph (vs,es) where
D xs bs = pairDesign 5
vs = [C] ++ [P x | x <- xs] ++ [B b | b <- bs]
es = L.sort $ [ [B a, B b] | a <- bs, b <- dropWhile (<=a) bs, disjoint a b]
++ [ [P p, B b] | b <- bs, p <- b]
++ [ [C, P p] | p <- xs ]
triples = combinationsOf 3 [1..7]
heptads = [ [a,b,c,d,e,f,g] | a <- triples,
b <- triples, a < b, meetOne b a,
c <- triples, b < c, all (meetOne c) [a,b],
d <- triples, c < d, all (meetOne d) [a,b,c],
e <- triples, d < e, all (meetOne e) [a,b,c,d],
f <- triples, e < f, all (meetOne f) [a,b,c,d,e],
g <- triples, f < g, all (meetOne g) [a,b,c,d,e,f],
foldl intersect [1..7] [a,b,c,d,e,f,g] == [] ]
where meetOne x y = length (intersect x y) == 1
plane +^ g = L.sort [line -^ g | line <- plane]
plane +^^ gs = orbit (+^) plane gs
hoffmanSingleton' = G.to1n hoffmanSingleton
hoffmanSingleton = graph (vs,es) where
h = head heptads
hs = h +^^ _A 7
vs = map Left hs ++ map Right triples
es = [ [Left h, Right t] | h <- hs, t <- triples, t `elem` h]
++ [ [Right t, Right t'] | t <- triples, t' <- dropWhile (<= t) triples, t `disjoint` t']
inducedA7 g = fromPairs [(v, v ~^ g) | v <- vs] where
vs = vertices hoffmanSingleton
(Left h) ~^ g = Left (h +^ g)
(Right t) ~^ g = Right (t -^ g)
hsA7 = toSn $ map inducedA7 $ _A 7
gewirtz' = G.to1n gewirtz
gewirtz = graph (vs,es) where
vs = [xs | xs <- blocks s_3_6_22, 22 `notElem` xs]
es = [ [v,v'] | v <- vs, v' <- dropWhile (<= v) vs, length (v `intersect` v') == 0]
data DesignVertex = C | P Integer | B [Integer] deriving (Eq,Ord,Show)
higmanSimsGraph' = G.to1n higmanSimsGraph
higmanSimsGraph = graph (vs,es) where
D xs bs = s_3_6_22
vs = [C] ++ [P x | x <- xs] ++ [B b | b <- bs]
es = L.sort $ [ [B a, B b] | a <- bs, b <- dropWhile (<=a) bs, disjoint a b]
++ [ [P p, B b] | b <- bs, p <- b]
++ [ [C, P p] | p <- xs ]
inducedM22 g = fromPairs [(v, v ~^ g) | v <- vs] where
vs = vertices higmanSimsGraph
(B b) ~^ g = B (b -^ g)
(P p) ~^ g = P (p .^ g)
C ~^ _ = C
higmanSimsM22 = toSn $ map inducedM22 $ m22sgs
_HS2 = SS.reduceGens $ graphAuts higmanSimsGraph
_HS = SS.derivedSubgp _HS2
sp2 r = graph (vs,es) where
vs = tail $ ptsAG (2*r) f2
es = [ [u,v] | [u,v] <- combinationsOf 2 vs, u <*>> n <.> v == 1]
n = fMatrix (2*r) (\i j -> if abs (ij) == 1 && even (max i j) then 1 else 0)
sp n | even n = sp2 (n `div` 2)
switch g us | us `D.isSubset` vs = graph (vs, L.sort switchedes) where
vs = vertices g
us' = vs L.\\ us
es = edges g
es' = S.fromList es
switchedes = [e | e@[v1,v2] <- es, (v1 `elem` us) == (v2 `elem` us)]
++ [ L.sort [v1,v2] | v1 <- us, v2 <- us', L.sort [v1,v2] `S.notMember` es']
schlafli' = G.to1n schlafli
schlafli = graph (vs,es') where
g = lineGraph $ k 8
v:vs = vertices g
es = edges g
gswitched = switch g (nbrs g v)
es' = edges gswitched
mcLaughlin' = G.to1n mcLaughlin
mcLaughlin = graph (vs',es') where
D xs bs = s_4_7_23
vs = map P xs ++ map B bs
es = [ [P x, B b] | x <- xs, b <- bs, x `notElem` b]
++ [ [B b1, B b2] | b1 <- bs, b2 <- bs, b1 < b2, length (b1 `intersect` b2) == 1]
g276 = graph (vs,es)
g276switched = switch g276 (nbrs g276 (P 0))
P 0 : vs' = vs
es' = edges g276switched
_McL2 = SS.reduceGens $ graphAuts mcLaughlin
_McL = SS.derivedSubgp $ _McL2