sym-0.4.1: Permutations, patterns, and statistics

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

Math.Sym.Internal

Contents

Description

An internal module used by the sym package.

A Lehmercode is a vector of integers w such w!i <= length w - 1 - i for each i in [0..length w - 1]; such a vector encodes a permutation. This module implements O(n) algorithms for unranking Lehmercodes and permutations; the algorithms are due to W. Myrvold and F. Ruskey [Ranking and Unranking Permutations in Linear Time, Information Processing Letters, 79 (2001) 281-284].

In addition, this module implements sorting operators, the symmetries in D8 acting on permutations, as well as most of the common permutation statistics.

Synopsis

Documentation

type Lehmercode = Vector IntSource

A Lehmercode is a vector of integers w such w!i <= length w - 1 - i for each i in [0..length w - 1].

type Perm0 = Vector IntSource

By convention, a member of Perm0 is a permutation of some finite subset of [0..].

Lehmercodes

unrankLehmercode :: Int -> Integer -> LehmercodeSource

unrankLehmercode n rank is the rank-th Lehmercode of length n.

fromLehmercode :: Lehmercode -> Perm0Source

Build a permutation from its Lehmercode.

randomLehmercode :: Int -> IO LehmercodeSource

A random Lehmercode of the given length.

lehmercodes :: Int -> [Lehmercode]Source

The list of Lehmercodes of a given length.

Permutations

size :: Perm0 -> IntSource

The size of a permutation; the number of elements.

toList :: Perm0 -> [Int]Source

The list of images of a permutation.

fromList :: [Int] -> Perm0Source

Make a permutation from a list of images.

act :: Perm0 -> Perm0 -> Perm0Source

act u v is the permutation w defined by w(u(i)) = v(i).

unrankPerm :: Int -> Integer -> Perm0Source

unrankPerm n rank is the rank-th (Myrvold & Ruskey) permutation of length n.

randomPerm :: Int -> IO Perm0Source

A random permutation of the given length.

sym :: Int -> [Perm0]Source

sym n is the list of permutations of [0..n-1] (the symmetric group).

idperm :: Int -> Perm0Source

The identity permutation of the given length.

revIdperm :: Int -> Perm0Source

The reverse of the identity permutation.

sti :: Perm0 -> Perm0Source

sti w is the inverse of the standardization of w (a permutation on [0..length w-1]). E.g., sti <4,9,2> == <2,0,1>.

st :: Perm0 -> Perm0Source

The standardization map.

ordiso :: Perm0 -> Perm0 -> Vector Int -> BoolSource

ordiso u v m determines whether the subword in v specified by m is order isomorphic to u.

simple :: Perm0 -> BoolSource

simple w determines whether w is simple

copies :: (Int -> Int -> [Vector Int]) -> Perm0 -> Perm0 -> [Vector Int]Source

copies subsets p w is the list of bitmasks that represent copies of p in w.

avoiders :: (Int -> Int -> [Vector Int]) -> (a -> Perm0) -> [Perm0] -> [a] -> [a]Source

avoiders subsets st ps ws is the list of permutations in ws avoiding the patterns in ps.

Permutation symmetries

reverse :: Perm0 -> Perm0Source

reverse <a_1,...,a_n> == <a_n,,...,a_1>. E.g., reverse <9,3,7,2> == <2,7,3,9>.

complement :: Perm0 -> Perm0Source

complement <a_1,...,a_n> == <b_1,,...,b_n>, where b_i = n - a_i - 1. E.g., complement <3,4,0,1,2> == <1,0,4,3,2>.

inverse :: Perm0 -> Perm0Source

inverse w is the group theoretical inverse of w. E.g., inverse <1,2,0> == <2,0,1>.

rotate :: Perm0 -> Perm0Source

The clockwise rotatation through 90 degrees. E.g., rotate <1,0,2> == <1,2,0>.

Permutation statistics

asc :: Perm0 -> IntSource

The number of ascents.

des :: Perm0 -> IntSource

The number of descents.

exc :: Perm0 -> IntSource

The number of excedances.

fp :: Perm0 -> IntSource

The number of fixed points.

cyc :: Perm0 -> IntSource

The number of cycles.

inv :: Perm0 -> IntSource

The number of inversions.

maj :: Perm0 -> IntSource

The major index.

comaj :: Perm0 -> IntSource

The co-major index.

peak :: Perm0 -> IntSource

The number of peaks.

vall :: Perm0 -> IntSource

The number of valleys.

dasc :: Perm0 -> IntSource

The number of double ascents.

ddes :: Perm0 -> IntSource

The number of double descents.

lmin :: Perm0 -> IntSource

The number of left-to-right minima.

lmax :: Perm0 -> IntSource

The number of left-to-right maxima.

rmin :: Perm0 -> IntSource

The number of left-to-right minima.

rmax :: Perm0 -> IntSource

The number of left-to-right maxima.

head :: Perm0 -> IntSource

First (left-most) value of a permutation.

last :: Perm0 -> IntSource

Last (right-most) value of a permutation.

lir :: Perm0 -> IntSource

The left-most increasing run.

ldr :: Perm0 -> IntSource

The left-most decreasing run.

rir :: Perm0 -> IntSource

The right-most increasing run.

rdr :: Perm0 -> IntSource

The right-most decreasing run.

comp :: Perm0 -> IntSource

The number of components.

scomp :: Perm0 -> IntSource

The number of skew components.

ep :: Perm0 -> IntSource

Rank as defined by Elizalde & Pak.

dim :: Perm0 -> IntSource

Dimension (largest non-fixed-point).

asc0 :: Perm0 -> IntSource

The number of small ascents.

des0 :: Perm0 -> IntSource

The number of small descents.

Left-to-right maxima, etc

lMaxima :: Perm0 -> Vector IntSource

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

rMaxima :: Perm0 -> Vector IntSource

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

Components

components :: Perm0 -> Vector IntSource

The set of indices of components.

Sorting operators

stackSort :: Perm0 -> Perm0Source

One pass of stack-sort.

bubbleSort :: Perm0 -> Perm0Source

One pass of bubble-sort.

Single point deletions

del :: Int -> Perm0 -> Perm0Source

Delete the element at a given position

Bitmasks

onesCUInt :: CUInt -> Vector IntSource

onesCUInt k m gives the k smallest indices whose bits are set in m.

nextCUInt :: CUInt -> CUIntSource

Lexicographically, the next CUInt with the same Hamming weight.

nextIntegral :: (Integral a, Bits a) => a -> aSource

Lexicographically, the next integral number with the same Hamming weight.