combinat-0.2.6.2: Generation of various combinatorial objects.

Safe HaskellNone
LanguageHaskell98

Math.Combinat.LatticePaths

Contents

Description

Dyck paths, lattice paths, etc

Synopsis

Types

data Step Source

A step in a lattice path

Constructors

UpStep

the step (1,1)

DownStep

the step (1,-1)

Instances

type LatticePath = [Step] Source

A lattice path is a path using only the allowed steps, never going below the zero level line y=0.

Note that if you rotate such a path by 45 degrees counterclockwise, you get a path which uses only the steps (1,0) and (0,1), and stays above the main diagonal (hence the name, we just use a different convention).

isValidPath :: LatticePath -> Bool Source

A lattice path is called "valid", if it never goes below the y=0 line.

isDyckPath :: LatticePath -> Bool Source

A Dyck path is a lattice path whose last point lies on the y=0 line

pathHeight :: LatticePath -> Int Source

Maximal height of a lattice path

pathEndpoint :: LatticePath -> (Int, Int) Source

Endpoint of a lattice path, which starts from (0,0).

pathCoordinates :: LatticePath -> [(Int, Int)] Source

Returns the coordinates of the path (excluding the starting point (0,0), but including the endpoint)

pathNumberOfPeaks :: LatticePath -> Int Source

Number of peaks of a path (excluding the endpoint)

pathNumberOfZeroTouches :: LatticePath -> Int Source

Number of points on the path which touch the y=0 zero level line (excluding the starting point (0,0), but including the endpoint; that is, for Dyck paths it this is always positive!).

pathNumberOfTouches' Source

Arguments

:: Int

h = the touch level

-> LatticePath 
-> Int 

Number of points on the path which touch the level line at height h (excluding the starting point (0,0), but including the endpoint).

Dyck paths

dyckPaths :: Int -> [LatticePath] Source

dyckPaths m lists all Dyck paths from (0,0) to (2m,0).

Remark: Dyck paths are obviously in bijection with nested parentheses, and thus also with binary trees.

Order is reverse lexicographical:

sort (dyckPaths m) == reverse (dyckPaths m)

dyckPathsNaive :: Int -> [LatticePath] Source

dyckPaths m lists all Dyck paths from (0,0) to (2m,0).

sort (dyckPathsNaive m) == sort (dyckPaths m) 

Naive recursive algorithm, order is ad-hoc

countDyckPaths :: Int -> Integer Source

The number of Dyck paths from (0,0) to (2m,0) is simply the m'th Catalan number.

nestedParensToDyckPath :: [Paren] -> LatticePath Source

The trivial bijection

dyckPathToNestedParens :: LatticePath -> [Paren] Source

The trivial bijection in the other direction

Bounded Dyck paths

boundedDyckPaths Source

Arguments

:: Int

h = maximum height

-> Int

m = half-length

-> [LatticePath] 

boundedDyckPaths h m lists all Dyck paths from (0,0) to (2m,0) whose height is at most h. Synonym for boundedDyckPathsNaive.

boundedDyckPathsNaive Source

Arguments

:: Int

h = maximum height

-> Int

m = half-length

-> [LatticePath] 

boundedDyckPathsNaive h m lists all Dyck paths from (0,0) to (2m,0) whose height is at most h.

sort (boundedDyckPaths h m) == sort [ p | p <- dyckPaths m , pathHeight p <= h ]
sort (boundedDyckPaths m m) == sort (dyckPaths m) 

Naive recursive algorithm, resulting order is pretty ad-hoc.

More general lattice paths

latticePaths :: (Int, Int) -> [LatticePath] Source

All lattice paths from (0,0) to (x,y). Clearly empty unless x-y is even. Synonym for latticePathsNaive

latticePathsNaive :: (Int, Int) -> [LatticePath] Source

All lattice paths from (0,0) to (x,y). Clearly empty unless x-y is even.

Note that

sort (dyckPaths n) == sort (latticePaths (0,2*n))

Naive recursive algorithm, resulting order is pretty ad-hoc.

Zero-level touches

touchingDyckPaths Source

Arguments

:: Int

k = number of touches

-> Int

m = half-length

-> [LatticePath] 

touchingDyckPaths k m lists all Dyck paths from (0,0) to (2m,0) which touch the zero level line y=0 exactly k times (excluding the starting point, but including the endpoint; thus, k should be positive). Synonym for touchingDyckPathsNaive.

touchingDyckPathsNaive Source

Arguments

:: Int

k = number of touches

-> Int

m = half-length

-> [LatticePath] 

touchingDyckPathsNaive k m lists all Dyck paths from (0,0) to (2m,0) which touch the zero level line y=0 exactly k times (excluding the starting point, but including the endpoint; thus, k should be positive).

sort (touchingDyckPathsNaive k m) == sort [ p | p <- dyckPaths m , pathNumberOfZeroTouches p == k ]

Naive recursive algorithm, resulting order is pretty ad-hoc.

Dyck paths with given number of peaks

peakingDyckPaths Source

Arguments

:: Int

k = number of peaks

-> Int

m = half-length

-> [LatticePath] 

peakingDyckPaths k m lists all Dyck paths from (0,0) to (2m,0) with exactly k peaks.

Synonym for peakingDyckPathsNaive

peakingDyckPathsNaive Source

Arguments

:: Int

k = number of peaks

-> Int

m = half-length

-> [LatticePath] 

peakingDyckPathsNaive k m lists all Dyck paths from (0,0) to (2m,0) with exactly k peaks.

sort (peakingDyckPathsNaive k m) = sort [ p | p <- dyckPaths m , pathNumberOfPeaks p == k ]

Naive recursive algorithm, resulting order is pretty ad-hoc.

countPeakingDyckPaths Source

Arguments

:: Int

k = number of peaks

-> Int

m = half-length

-> Integer 

Dyck paths of length 2m with k peaks are counted by the Narayana numbers N(m,k) = binom{m}{k} binom{m}{k-1} / m

Random lattice paths

randomDyckPath :: RandomGen g => Int -> g -> (LatticePath, g) Source

A uniformly random Dyck path of length 2m