Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- unRight :: Ord a1 => Permutation (Either a2 a1) -> Permutation a1
- restrictLeft :: Ord a => Permutation (Either a b) -> Permutation a
- ptStab :: (Show a, Foldable t, Ord a) => [Permutation a] -> t a -> [Permutation a]
- isTransitive :: Ord t => [Permutation t] -> Bool
- transitiveConstituentHomomorphism :: (Ord a, Show a) => [Permutation a] -> [a] -> ([Permutation a], [Permutation a])
- transitiveConstituentHomomorphism' :: (Foldable t, Show b, Ord b) => [Permutation b] -> t b -> ([Permutation b], [Permutation b])
- minimalBlock :: Ord a => [Permutation a] -> [a] -> [[a]]
- blockSystems :: Ord t => [Permutation t] -> [[[t]]]
- blockSystemsSGS :: Ord a => [Permutation a] -> [[[a]]]
- isPrimitive :: Ord t => [Permutation t] -> Bool
- isPrimitiveSGS :: Ord a => [Permutation a] -> Bool
- blockHomomorphism :: (Ord t, Show t) => [Permutation t] -> [[t]] -> ([Permutation t], [Permutation [t]])
- blockHomomorphism' :: (Show b, Ord b) => [Permutation b] -> [[b]] -> ([Permutation b], [Permutation [b]])
- normalClosure :: (Show a, Ord a) => [Permutation a] -> [Permutation a] -> [Permutation a]
- intersectionNormalClosure :: (Show a, Ord a) => [Permutation a] -> [Permutation a] -> [Permutation a]
- centralizerSymTrans :: (Show a, Ord a) => [Permutation a] -> [Permutation a]
Documentation
unRight :: Ord a1 => Permutation (Either a2 a1) -> Permutation a1 Source #
restrictLeft :: Ord a => Permutation (Either a b) -> Permutation a Source #
ptStab :: (Show a, Foldable t, Ord a) => [Permutation a] -> t a -> [Permutation a] Source #
isTransitive :: Ord t => [Permutation t] -> Bool Source #
transitiveConstituentHomomorphism :: (Ord a, Show a) => [Permutation a] -> [a] -> ([Permutation a], [Permutation a]) Source #
Given a group gs and a transitive constituent ys, return the kernel and image of the transitive constituent homomorphism. That is, suppose that gs acts on a set xs, and ys is a subset of xs on which gs acts transitively. Then the transitive constituent homomorphism is the restriction of the action of gs to an action on the ys.
transitiveConstituentHomomorphism' :: (Foldable t, Show b, Ord b) => [Permutation b] -> t b -> ([Permutation b], [Permutation b]) Source #
minimalBlock :: Ord a => [Permutation a] -> [a] -> [[a]] Source #
blockSystems :: Ord t => [Permutation t] -> [[[t]]] Source #
Given a transitive group gs, find all non-trivial block systems. That is, if gs act on xs, find all the ways that the xs can be divided into blocks, such that the gs also have a permutation action on the blocks
blockSystemsSGS :: Ord a => [Permutation a] -> [[[a]]] Source #
A more efficient version of blockSystems, if we have an sgs
isPrimitive :: Ord t => [Permutation t] -> Bool Source #
A permutation group is primitive if it has no non-trivial block systems
isPrimitiveSGS :: Ord a => [Permutation a] -> Bool Source #
blockHomomorphism :: (Ord t, Show t) => [Permutation t] -> [[t]] -> ([Permutation t], [Permutation [t]]) Source #
Given a transitive group gs, and a block system for gs, return the kernel and image of the block homomorphism (the homomorphism onto the action of gs on the blocks)
blockHomomorphism' :: (Show b, Ord b) => [Permutation b] -> [[b]] -> ([Permutation b], [Permutation [b]]) Source #
normalClosure :: (Show a, Ord a) => [Permutation a] -> [Permutation a] -> [Permutation a] Source #
intersectionNormalClosure :: (Show a, Ord a) => [Permutation a] -> [Permutation a] -> [Permutation a] Source #
centralizerSymTrans :: (Show a, Ord a) => [Permutation a] -> [Permutation a] Source #