Safe Haskell | Safe-Infered |
---|
Math.Combinatorics.Design
Description
A module for constructing and working with combinatorial designs.
Given integers t < k < v and lambda > 0, a t-design or t-(v,k,lambda) design is an incidence structure of points X and blocks B, where X is a set of v points, B is a collection of k-subsets of X, with the property that any t points are contained in exactly lambda blocks. If lambda = 1 and t >= 2, then a t-design is also called a Steiner system S(t,k,v).
Many designs are highly symmetric structures, having large automorphism groups. In particular, the Mathieu groups, which were the first discovered sporadic finite simple groups, turn up as the automorphism groups of the Witt designs.
- isSubset :: Eq a => [a] -> [a] -> Bool
- data Design a = D [a] [[a]]
- design :: Ord a => ([a], [[a]]) -> Design a
- toDesign :: Ord a => ([a], [[a]]) -> Design a
- isValid :: Ord a => Design a -> Bool
- points :: Design t -> [t]
- blocks :: Design t -> [[t]]
- noRepeatedBlocks :: Ord t => Design t -> Bool
- tDesignParams :: Eq a => Int -> Design a -> Maybe (Int, Int, Int)
- findvk :: Design a -> Maybe (Int, Int)
- findlambda :: Eq a => Int -> Design a -> Maybe Int
- designParams :: Eq a => Design a -> Maybe (Int, (Int, Int, Int))
- isStructure :: Eq a => Int -> Design a -> Bool
- isDesign :: Ord a => Int -> Design a -> Bool
- is2Design :: Ord a => Design a -> Bool
- isSquare :: Ord a => Design a -> Bool
- incidenceMatrix :: Eq t => Design t -> [[Int]]
- subsetDesign :: (Enum a, Num a, Ord a) => a -> Int -> Design a
- pairDesign :: Integral a => a -> Design a
- ag2 :: (FiniteField k, Ord k) => [k] -> Design [k]
- pg2 :: (FiniteField k, Ord k) => [k] -> Design [k]
- flatsDesignPG :: (Num a, Ord a, FinSet a) => Int -> [a] -> Int -> Design [a]
- pg :: (Num a, Ord a, FinSet a) => Int -> [a] -> Design [a]
- flatsDesignAG :: (Num a, Ord a, FinSet a) => Int -> [a] -> Int -> Design [a]
- ag :: (Num a, Ord a, FinSet a) => Int -> [a] -> Design [a]
- to1n :: (Enum a1, Num a1, Ord a) => Design a -> Design a1
- paleyDesign :: (Num a, Ord a) => [a] -> Design a
- fanoPlane :: Design F7
- dual :: Ord t => Design t -> Design [t]
- derivedDesign :: Ord t => Design t -> t -> Design t
- pointResidual :: Ord t => Design t -> t -> Design t
- complementaryDesign :: Ord a => Design a -> Design a
- blockResidual :: Ord t => Design t -> [t] -> Design t
- isDesignAut :: Ord a => Design a -> Permutation a -> Bool
- incidenceGraph :: Ord a => Design a -> Graph (Either a [a])
- designAuts :: Ord t => Design t -> [Permutation t]
- designAuts1 :: (Ord a, Show a) => Design a -> [Permutation a]
- alphaL2_23 :: Permutation Integer
- betaL2_23 :: Permutation Integer
- gammaL2_23 :: Permutation Integer
- l2_23 :: [Permutation Integer]
- deltaM24 :: Permutation Integer
- m24 :: [Permutation Integer]
- m24sgs :: [Permutation Integer]
- m23sgs :: [Permutation Integer]
- m22sgs :: [Permutation Integer]
- octad :: [Integer]
- s_5_8_24 :: Design Integer
- s_4_7_23 :: Design Integer
- s_3_6_22 :: Design Integer
- s_5_8_24' :: Design Integer
- alphaL2_11 :: Permutation Integer
- betaL2_11 :: Permutation Integer
- gammaL2_11 :: Permutation Integer
- l2_11 :: [Permutation Integer]
- deltaM12 :: Permutation Integer
- hexad :: [Integer]
- s_5_6_12 :: Design Integer
- s_4_5_11 :: Design Integer
- m12 :: [Permutation Integer]
- m12sgs :: [Permutation Integer]
- m11sgs :: [Permutation Integer]
Documentation
Constructors
D [a] [[a]] |
noRepeatedBlocks :: Ord t => Design t -> BoolSource
incidenceMatrix :: Eq t => Design t -> [[Int]]Source
The incidence matrix of a design, with rows indexed by blocks and columns by points. (Note that in the literature, the opposite convention is sometimes used instead.)
pairDesign :: Integral a => a -> Design aSource
ag2 :: (FiniteField k, Ord k) => [k] -> Design [k]Source
The affine plane AG(2,Fq), a 2-(q^2,q,1) design or Steiner system S(2,q,q^2).
pg2 :: (FiniteField k, Ord k) => [k] -> Design [k]Source
The projective plane PG(2,Fq), a square 2-(q^2+q+1,q+1,1) design or Steiner system S(2,q+1,q^2+q+1).
For example, pg2 f2
is the Fano plane, a Steiner triple system S(2,3,7).
paleyDesign :: (Num a, Ord a) => [a] -> Design aSource
derivedDesign :: Ord t => Design t -> t -> Design tSource
pointResidual :: Ord t => Design t -> t -> Design tSource
complementaryDesign :: Ord a => Design a -> Design aSource
blockResidual :: Ord t => Design t -> [t] -> Design tSource
isDesignAut :: Ord a => Design a -> Permutation a -> BoolSource
designAuts :: Ord t => Design t -> [Permutation t]Source
Find a strong generating set for the automorphism group of a design
designAuts1 :: (Ord a, Show a) => Design a -> [Permutation a]Source
m24 :: [Permutation Integer]Source
Generators for the Mathieu group M24, a finite simple group of order 244823040
m24sgs :: [Permutation Integer]Source
A strong generating set for the Mathieu group M24, a finite simple group of order 244823040
m23sgs :: [Permutation Integer]Source
A strong generating set for the Mathieu group M23, a finite simple group of order 10200960
m22sgs :: [Permutation Integer]Source
A strong generating set for the Mathieu group M22, a finite simple group of order 443520
s_5_8_24 :: Design IntegerSource
The Steiner system S(5,8,24), with 759 blocks, whose automorphism group is M24
s_4_7_23 :: Design IntegerSource
The Steiner system S(4,7,23), with 253 blocks, whose automorphism group is M23
s_3_6_22 :: Design IntegerSource
The Steiner system S(3,6,22), with 77 blocks, whose automorphism group is M22
s_5_6_12 :: Design IntegerSource
The Steiner system S(5,6,12), with 132 blocks, whose automorphism group is M12
s_4_5_11 :: Design IntegerSource
The Steiner system S(4,5,11), with 66 blocks, whose automorphism group is M11
m12 :: [Permutation Integer]Source
Generators for the Mathieu group M12, a finite simple group of order 95040
m12sgs :: [Permutation Integer]Source
A strong generating set for the Mathieu group M12, a finite simple group of order 95040
m11sgs :: [Permutation Integer]Source
A strong generating set for the Mathieu group M11, a finite simple group of order 7920