sym-0.8: Permutations, patterns, and statistics

MaintainerAnders Claesson <anders.claesson@gmail.com>
Safe HaskellNone

Math.Sym

Contents

Description

Provides an efficient definition of standard permutations, StPerm, together with an abstract class, Perm, whose functionality is largely inherited from StPerm using a group action and the standardization map.

Synopsis

Standard permutations

data StPerm Source

By a standard permutation we shall mean a permutations of [0..k-1].

toList :: StPerm -> [Int]Source

Convert a standard permutation to a list.

fromList :: [Int] -> StPermSource

Convert a list to a standard permutation. The list should a permutation of the elements [0..k-1] for some positive k. No checks for this are done.

sym :: Int -> [StPerm]Source

The list of standard permutations of the given size (the symmetric group). E.g.,

 sym 2 == [fromList [0,1], fromList [1,0]]

The permutation typeclass

class Ord a => Perm a whereSource

The class of permutations. Minimal complete definition: st, act and idperm. The default implementation of size can be somewhat slow, so you may want to implement it as well.

Methods

st :: a -> StPermSource

The standardization map. If there is an underlying linear order on a then st is determined by the unique order preserving map from [0..] to that order. In any case, the standardization map should be equivariant with respect to the group action defined below; i.e., it should hold that

 st (u `act` v) == u `act` st v

act :: StPerm -> a -> aSource

A (left) group action of StPerm on a. As for any group action it should hold that

 (u `act` v) `act` w == u `act` (v `act` w)   &&   idperm n `act` v == v

where v,w::a and u::StPerm are of size n.

size :: a -> IntSource

The size of a permutation. The default implementation derived from

 size == size . st

This is not a circular definition as size on StPerm is implemented independently. If the implementation of st is slow, then it can be worth while to override the standard definiton; any implementation should, however, satisfy the identity above.

idperm :: Int -> aSource

The identity permutation of the given size.

inverse :: a -> aSource

The group theoretical inverse. It should hold that

 inverse == unst . inverse . st

and this is the default implementation.

ordiso :: StPerm -> a -> BoolSource

Predicate determining if two permutations are order-isomorphic. The default implementation uses

 u `ordiso` v  ==  u == st v

Equivalently, one could use

 u `ordiso` v  ==  inverse u `act` v == idperm (size u)

unstn :: Int -> StPerm -> aSource

The inverse of the standardization function. For efficiency reasons we make the size of the permutation an argument to this function. It should hold that

 unst n w == w `act` idperm n

and this is the default implementation. An un-standardization function without the size argument is given by unst below.

unst :: Perm a => StPerm -> aSource

The inverse of st. It should hold that

 unst w == unstn (size w) w

and this is the default implementation.

newtype CharPerm Source

A String viewed as a permutation of its characters. The alphabet is ordered as

 ['1'..'9'] ++ ['A'..'Z'] ++ ['a'..]

Constructors

CharPerm 

Fields

chars :: String
 

newtype IntPerm Source

A list of integers viewed as a permutation.

Constructors

IntPerm 

Fields

ints :: [Int]
 

IntMaps as permutations

newtype Perm2 Source

Type alias for IntMap Int. This can be thought of as a permutations in two line notation.

Constructors

Perm2 

Fields

intmap :: IntMap Int
 

Convenience functions

empty :: Perm a => aSource

The empty permutation.

one :: Perm a => aSource

The one letter permutation.

toVector :: Perm a => a -> Vector IntSource

Convert a permutation to a vector.

fromVector :: Perm a => Vector Int -> aSource

Convert a vector to a permutation. The vector should be a permutation of the elements [0..k-1] for some positive k. No checks for this are done.

bijection :: Perm a => a -> Int -> IntSource

The bijective function defined by a permutation.

lift :: (Perm a, Perm b) => (Vector Int -> Vector Int) -> a -> bSource

Lift a function on 'Vector Int' to a function on any permutations:

 lift f = fromVector . f . toVector

lift2 :: (Perm a, Perm b, Perm c) => (Vector Int -> Vector Int -> Vector Int) -> a -> b -> cSource

Like lift but for functions of two variables

normalize :: Perm a => [a] -> [a]Source

Sort a list of permutations with respect to the standardization and remove duplicates

cast :: (Perm a, Perm b) => a -> bSource

Cast a permutation of one type to another

Constructions

(/+/) :: Perm a => a -> a -> aSource

The direct sum of two permutations.

dsum :: Perm a => [a] -> aSource

The direct sum of a list of permutations.

(\-\) :: Perm a => a -> a -> aSource

The skew sum of two permutations.

ssum :: Perm a => [a] -> aSource

The skew sum of a list of permutations.

inflate :: (Perm a, Perm b) => b -> [a] -> aSource

inflate w vs is the inflation of w by vs. It is the permutation of length sum (map size vs) obtained by replacing each entry w!i by an interval that is order isomorphic to vs!i in such a way that the intervals are order isomorphic to w. In particular,

 u /+/ v == inflate "12" [u,v]
 u \-\ v == inflate "21" [u,v]

Generating permutations

unrankPerm :: Perm a => Int -> Integer -> aSource

unrankPerm u rank is the rank-th (Myrvold & Ruskey) permutation of size n. E.g.,

 unrankPerm 9 88888 == "561297843"

randomPerm :: Perm a => Int -> IO aSource

randomPerm n is a random permutation of size n.

perms :: Perm a => Int -> [a]Source

All permutations of a given size. E.g.,

 perms 3 == ["123","213","321","132","231","312"]

Sorting operators

stackSort :: Perm a => a -> aSource

One pass of stack-sort.

bubbleSort :: Perm a => a -> aSource

One pass of bubble-sort.

Permutation patterns

class Perm a => Pattern a whereSource

All methods of the Pattern typeclass have default implementations. This is because any permutation can also be seen as a pattern. If you want to override the default implementation you should at least define copiesOf.

Methods

copiesOf :: Perm b => a -> b -> [Set]Source

copiesOf p w is the list of indices of copies of the pattern p in the permutation w. E.g.,

 copiesOf "21" "2431" == [fromList [1,2],fromList [0,3],fromList [1,3],fromList [2,3]]

contains :: Perm b => b -> a -> BoolSource

w contains p is a predicate determining if w contains the pattern p.

avoids :: Perm b => b -> a -> BoolSource

w avoids p is a predicate determining if w avoids the pattern p.

avoidsAll :: Perm b => b -> [a] -> BoolSource

w avoidsAll ps is a predicate determining if w avoids the patterns ps.

avoiders :: Perm b => [a] -> [b] -> [b]Source

avoiders ps vs is the list of permutations in vs avoiding the patterns ps. The default definition is

 avoiders ps = filter (`avoidsAll` ps)

stat :: (Pattern a, Perm b) => a -> b -> IntSource

stat p is the pattern p when regarded as a statistic/function counting copies of itself:

 stat p = length . copiesOf p

av :: Pattern a => [a] -> Int -> [StPerm]Source

av ps n is the list of permutations of [0..n-1] avoiding the patterns ps. E.g.,

 map (length . av ["132","321"]) [1..8] == [1,2,4,7,11,16,22,29]

permClass :: (Pattern a, Perm b) => [a] -> Int -> [b]Source

Like av but the return type is any set of permutations.

Poset functions

del :: Perm a => Int -> a -> aSource

Delete the element at a given position

shadow :: Perm a => [a] -> [a]Source

The list of all single point deletions

downset :: Perm a => [a] -> [a]Source

The list of permutations that are contained in at least one of the given permutaions

ext :: Perm a => Int -> Int -> a -> aSource

ext i j w extends w by inserting a new element of (relative) size j at position i. It should hold that 0 <= i,j <= size w.

coshadow :: Perm a => [a] -> [a]Source

The list of all single point extensions

minima :: Pattern a => [a] -> [a]Source

The set of minimal elements with respect to containment.

maxima :: Pattern a => [a] -> [a]Source

The set of maximal elements with respect to containment.

coeff :: Pattern a => (a -> Int) -> a -> IntSource

coeff f v is the coefficient of v when expanding the permutation statistic f as a sum of permutations/patterns. See Petter Brändén and Anders Claesson: Mesh patterns and the expansion of permutation statistics as sums of permutation patterns, The Electronic Journal of Combinatorics 18(2) (2011), http://www.combinatorics.org/ojs/index.php/eljc/article/view/v18i2p5.

Left-to-right maxima and similar functions

lMaxima :: Perm a => a -> SetSource

The set of indices of left-to-right maxima.

lMinima :: Perm a => a -> SetSource

The set of indices of left-to-right minima.

rMaxima :: Perm a => a -> SetSource

The set of indices of right-to-left maxima.

rMinima :: Perm a => a -> SetSource

The set of indices of right-to-left minima.

Components and skew components

components :: Perm a => a -> SetSource

The set of indices of components.

skewComponents :: Perm a => a -> SetSource

The set of indices of skew components.

Simple permutations

simple :: Perm a => a -> BoolSource

A predicate determining if a given permutation is simple.

Subsets

type Set = Vector IntSource

A set is represented by an increasing vector of non-negative integers.

subsets :: Int -> Int -> [Set]Source

subsets n k is the list of subsets of [0..n-1] with k elements.