sym-0.4.2: 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].

toVector :: StPerm -> Vector IntSource

Convert a standard permutation to a vector.

fromVector :: Vector Int -> StPermSource

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

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.

(/-/) :: StPerm -> StPerm -> StPermSource

The skew sum of two permutations. (A definition of the direct sum is provided by mappend of the Monoid instance for StPerm.)

bijection :: StPerm -> Int -> IntSource

The bijective function defined by a standard permutation.

unrankStPerm :: Int -> Integer -> StPermSource

unrankStPerm n rank is the rank-th (Myrvold & Ruskey) permutation of [0..n-1]. E.g.,

 unrankStPerm 16 19028390 == fromList [6,15,4,11,7,8,9,2,5,0,10,3,12,13,14,1]

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 Perm a whereSource

The class of permutations. Minimal complete definition: st act and idperm. The default implementations of size and neutralize can be somewhat slow, so you may want to implement them 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)   &&   neutralize u `act` v == v

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.

neutralize :: a -> aSource

The permutation obtained by acting on the given permutation with its own inverse; that is, the identity permutation on the same underlying set as the given permutation. It should hold that

 st (neutralize u) == neutralize (st u)
 neutralize u == inverse (st u) `act` u
 neutralize u == idperm (size u)

The default implementation uses the last of these three equations.

inverse :: a -> aSource

The group theoretical inverse. It should hold that

 inverse u == inverse (st u) `act` neutralize u

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 == neutralize v

Instances

Generalize

generalize :: Perm a => (StPerm -> StPerm) -> a -> aSource

Generalize a function on StPerm to a function on any permutations:

 generalize f v = f (st v) `act` neutralize v

Note that this will only work as intended if f is size preserving.

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

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

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

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

avoids :: Perm a => a -> [StPerm] -> BoolSource

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

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

avoiders ps vs is the list of permutations in vs avoiding the patterns ps. This is equivalent to the definition

 avoiders ps = filter (`avoids` ps)

but is usually much faster.

av :: [StPerm] -> Int -> [StPerm]Source

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

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

Single point extensions and deletions

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

Delete the element at a given position

shadow :: (Ord a, Perm a) => a -> [a]Source

The list of all single point deletions

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

Extend a permutation by inserting a new largest element at the given position

coshadow :: (Ord a, Perm a) => a -> [a]Source

The list of all single point extensions

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.