{-# LANGUAGE BangPatterns #-}
module Math.Combinat.Partitions.NonCrossing where
import Control.Applicative
import Data.List
import Data.Ord
import System.Random
import Math.Combinat.Numbers
import Math.Combinat.LatticePaths
import Math.Combinat.Helper
import Math.Combinat.Partitions.Set
import Math.Combinat.Classes
newtype NonCrossing = NonCrossing [[Int]] deriving (NonCrossing -> NonCrossing -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonCrossing -> NonCrossing -> Bool
$c/= :: NonCrossing -> NonCrossing -> Bool
== :: NonCrossing -> NonCrossing -> Bool
$c== :: NonCrossing -> NonCrossing -> Bool
Eq,Eq NonCrossing
NonCrossing -> NonCrossing -> Bool
NonCrossing -> NonCrossing -> Ordering
NonCrossing -> NonCrossing -> NonCrossing
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: NonCrossing -> NonCrossing -> NonCrossing
$cmin :: NonCrossing -> NonCrossing -> NonCrossing
max :: NonCrossing -> NonCrossing -> NonCrossing
$cmax :: NonCrossing -> NonCrossing -> NonCrossing
>= :: NonCrossing -> NonCrossing -> Bool
$c>= :: NonCrossing -> NonCrossing -> Bool
> :: NonCrossing -> NonCrossing -> Bool
$c> :: NonCrossing -> NonCrossing -> Bool
<= :: NonCrossing -> NonCrossing -> Bool
$c<= :: NonCrossing -> NonCrossing -> Bool
< :: NonCrossing -> NonCrossing -> Bool
$c< :: NonCrossing -> NonCrossing -> Bool
compare :: NonCrossing -> NonCrossing -> Ordering
$ccompare :: NonCrossing -> NonCrossing -> Ordering
Ord,Int -> NonCrossing -> ShowS
[NonCrossing] -> ShowS
NonCrossing -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NonCrossing] -> ShowS
$cshowList :: [NonCrossing] -> ShowS
show :: NonCrossing -> String
$cshow :: NonCrossing -> String
showsPrec :: Int -> NonCrossing -> ShowS
$cshowsPrec :: Int -> NonCrossing -> ShowS
Show,ReadPrec [NonCrossing]
ReadPrec NonCrossing
Int -> ReadS NonCrossing
ReadS [NonCrossing]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NonCrossing]
$creadListPrec :: ReadPrec [NonCrossing]
readPrec :: ReadPrec NonCrossing
$creadPrec :: ReadPrec NonCrossing
readList :: ReadS [NonCrossing]
$creadList :: ReadS [NonCrossing]
readsPrec :: Int -> ReadS NonCrossing
$creadsPrec :: Int -> ReadS NonCrossing
Read)
_isNonCrossing :: [[Int]] -> Bool
_isNonCrossing :: [[Int]] -> Bool
_isNonCrossing [[Int]]
zzs0 = [[Int]] -> Bool
_isNonCrossingUnsafe ([[Int]] -> [[Int]]
_standardizeNonCrossing [[Int]]
zzs0)
_isNonCrossingUnsafe :: [[Int]] -> Bool
_isNonCrossingUnsafe :: [[Int]] -> Bool
_isNonCrossingUnsafe [[Int]]
zzs =
case [[Int]] -> Maybe LatticePath
_nonCrossingPartitionToDyckPathMaybe [[Int]]
zzs of
Maybe LatticePath
Nothing -> Bool
False
Just LatticePath
dyck -> case LatticePath -> Maybe NonCrossing
dyckPathToNonCrossingPartitionMaybe LatticePath
dyck of
Maybe NonCrossing
Nothing -> Bool
False
Just (NonCrossing [[Int]]
yys) -> [[Int]]
yys forall a. Eq a => a -> a -> Bool
== [[Int]]
zzs
_standardizeNonCrossing :: [[Int]] -> [[Int]]
_standardizeNonCrossing :: [[Int]] -> [[Int]]
_standardizeNonCrossing = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing forall {a}. [a] -> a
myhead) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a. Ord a => [a] -> [a]
reverseSort where
myhead :: [a] -> a
myhead [a]
xs = case [a]
xs of
(a
x:[a]
xs) -> a
x
[] -> forall a. HasCallStack => String -> a
error String
"_standardizeNonCrossing: empty subset"
fromNonCrossing :: NonCrossing -> [[Int]]
fromNonCrossing :: NonCrossing -> [[Int]]
fromNonCrossing (NonCrossing [[Int]]
xs) = [[Int]]
xs
toNonCrossingUnsafe :: [[Int]] -> NonCrossing
toNonCrossingUnsafe :: [[Int]] -> NonCrossing
toNonCrossingUnsafe = [[Int]] -> NonCrossing
NonCrossing
toNonCrossing :: [[Int]] -> NonCrossing
toNonCrossing :: [[Int]] -> NonCrossing
toNonCrossing [[Int]]
xxs = case [[Int]] -> Maybe NonCrossing
toNonCrossingMaybe [[Int]]
xxs of
Just NonCrossing
nc -> NonCrossing
nc
Maybe NonCrossing
Nothing -> forall a. HasCallStack => String -> a
error String
"toNonCrossing: not a non-crossing partition"
toNonCrossingMaybe :: [[Int]] -> Maybe NonCrossing
toNonCrossingMaybe :: [[Int]] -> Maybe NonCrossing
toNonCrossingMaybe [[Int]]
xxs0 =
if [[Int]] -> Bool
_isNonCrossingUnsafe [[Int]]
xxs
then forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [[Int]] -> NonCrossing
NonCrossing [[Int]]
xxs
else forall a. Maybe a
Nothing
where
xxs :: [[Int]]
xxs = [[Int]] -> [[Int]]
_standardizeNonCrossing [[Int]]
xxs0
setPartitionToNonCrossing :: SetPartition -> Maybe NonCrossing
setPartitionToNonCrossing :: SetPartition -> Maybe NonCrossing
setPartitionToNonCrossing (SetPartition [[Int]]
zzs0) =
if [[Int]] -> Bool
_isNonCrossingUnsafe [[Int]]
zzs
then forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [[Int]] -> NonCrossing
NonCrossing [[Int]]
zzs
else forall a. Maybe a
Nothing
where
zzs :: [[Int]]
zzs = [[Int]] -> [[Int]]
_standardizeNonCrossing [[Int]]
zzs0
instance HasNumberOfParts NonCrossing where
numberOfParts :: NonCrossing -> Int
numberOfParts (NonCrossing [[Int]]
p) = forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Int]]
p
dyckPathToNonCrossingPartition :: LatticePath -> NonCrossing
dyckPathToNonCrossingPartition :: LatticePath -> NonCrossing
dyckPathToNonCrossingPartition = [[Int]] -> NonCrossing
NonCrossing forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go Int
0 [] [] [] where
go :: Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go :: Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go !Int
cnt [Int]
stack [Int]
small [[Int]]
big LatticePath
path =
case LatticePath
path of
(Step
x:LatticePath
xs) -> case Step
x of
Step
UpStep -> let cnt' :: Int
cnt' = Int
cnt forall a. Num a => a -> a -> a
+ Int
1 in case LatticePath
xs of
(Step
y:LatticePath
ys) -> case Step
y of
Step
UpStep -> Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go Int
cnt' (Int
cnt'forall a. a -> [a] -> [a]
:[Int]
stack) [Int]
small [[Int]]
big LatticePath
xs
Step
DownStep -> Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go Int
cnt' (Int
cnt'forall a. a -> [a] -> [a]
:[Int]
stack) [] (forall a. [a] -> [a]
reverse [Int]
small forall a. a -> [a] -> [a]
: [[Int]]
big) LatticePath
xs
[] -> forall a. HasCallStack => String -> a
error String
"dyckPathToNonCrossingPartition: last step is an UpStep (thus input was not a Dyck path)"
Step
DownStep -> case [Int]
stack of
(Int
k:[Int]
ks) -> Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go Int
cnt [Int]
ks (Int
kforall a. a -> [a] -> [a]
:[Int]
small) [[Int]]
big LatticePath
xs
[] -> forall a. HasCallStack => String -> a
error String
"dyckPathToNonCrossingPartition: empty stack, shouldn't happen (thus input was not a Dyck path)"
[] -> forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse (forall a. [a] -> [a]
reverse [Int]
small forall a. a -> [a] -> [a]
: [[Int]]
big)
dyckPathToNonCrossingPartitionMaybe :: LatticePath -> Maybe NonCrossing
dyckPathToNonCrossingPartitionMaybe :: LatticePath -> Maybe NonCrossing
dyckPathToNonCrossingPartitionMaybe = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [[Int]] -> NonCrossing
NonCrossing forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go Int
0 [] [] [] where
go :: Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go :: Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go !Int
cnt [Int]
stack [Int]
small [[Int]]
big LatticePath
path =
case LatticePath
path of
(Step
x:LatticePath
xs) -> case Step
x of
Step
UpStep -> let cnt' :: Int
cnt' = Int
cnt forall a. Num a => a -> a -> a
+ Int
1 in case LatticePath
xs of
(Step
y:LatticePath
ys) -> case Step
y of
Step
UpStep -> Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go Int
cnt' (Int
cnt'forall a. a -> [a] -> [a]
:[Int]
stack) [Int]
small [[Int]]
big LatticePath
xs
Step
DownStep -> Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go Int
cnt' (Int
cnt'forall a. a -> [a] -> [a]
:[Int]
stack) [] (forall a. [a] -> [a]
reverse [Int]
small forall a. a -> [a] -> [a]
: [[Int]]
big) LatticePath
xs
[] -> forall a. Maybe a
Nothing
Step
DownStep -> case [Int]
stack of
(Int
k:[Int]
ks) -> Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go Int
cnt [Int]
ks (Int
kforall a. a -> [a] -> [a]
:[Int]
small) [[Int]]
big LatticePath
xs
[] -> forall a. Maybe a
Nothing
[] -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse (forall a. [a] -> [a]
reverse [Int]
small forall a. a -> [a] -> [a]
: [[Int]]
big)
nonCrossingPartitionToDyckPath :: NonCrossing -> LatticePath
nonCrossingPartitionToDyckPath :: NonCrossing -> LatticePath
nonCrossingPartitionToDyckPath (NonCrossing [[Int]]
zzs) = Int -> [[Int]] -> LatticePath
go Int
0 [[Int]]
zzs where
go :: Int -> [[Int]] -> LatticePath
go !Int
k (ys :: [Int]
ys@(Int
y:[Int]
_):[[Int]]
yys) = forall a. Int -> a -> [a]
replicate (Int
yforall a. Num a => a -> a -> a
-Int
k) Step
UpStep forall a. [a] -> [a] -> [a]
++ forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
ys) Step
DownStep forall a. [a] -> [a] -> [a]
++ Int -> [[Int]] -> LatticePath
go Int
y [[Int]]
yys
go !Int
k [] = []
go Int
_ [[Int]]
_ = forall a. HasCallStack => String -> a
error String
"nonCrossingPartitionToDyckPath: shouldnt't happen"
_nonCrossingPartitionToDyckPathMaybe :: [[Int]] -> Maybe LatticePath
_nonCrossingPartitionToDyckPathMaybe :: [[Int]] -> Maybe LatticePath
_nonCrossingPartitionToDyckPathMaybe = Int -> [[Int]] -> Maybe LatticePath
go Int
0 where
go :: Int -> [[Int]] -> Maybe LatticePath
go !Int
k (ys :: [Int]
ys@(Int
y:[Int]
_):[[Int]]
yys) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\LatticePath
zs -> forall a. Int -> a -> [a]
replicate (Int
yforall a. Num a => a -> a -> a
-Int
k) Step
UpStep forall a. [a] -> [a] -> [a]
++ forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
ys) Step
DownStep forall a. [a] -> [a] -> [a]
++ LatticePath
zs) (Int -> [[Int]] -> Maybe LatticePath
go Int
y [[Int]]
yys)
go !Int
k [] = forall a. a -> Maybe a
Just []
go Int
_ [[Int]]
_ = forall a. Maybe a
Nothing
nonCrossingPartitions :: Int -> [NonCrossing]
nonCrossingPartitions :: Int -> [NonCrossing]
nonCrossingPartitions = forall a b. (a -> b) -> [a] -> [b]
map LatticePath -> NonCrossing
dyckPathToNonCrossingPartition forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [LatticePath]
dyckPaths
nonCrossingPartitionsWithKParts
:: Int
-> Int
-> [NonCrossing]
nonCrossingPartitionsWithKParts :: Int -> Int -> [NonCrossing]
nonCrossingPartitionsWithKParts Int
k Int
n = forall a b. (a -> b) -> [a] -> [b]
map LatticePath -> NonCrossing
dyckPathToNonCrossingPartition forall a b. (a -> b) -> a -> b
$ Int -> Int -> [LatticePath]
peakingDyckPaths Int
k Int
n
countNonCrossingPartitions :: Int -> Integer
countNonCrossingPartitions :: Int -> Integer
countNonCrossingPartitions = Int -> Integer
countDyckPaths
countNonCrossingPartitionsWithKParts
:: Int
-> Int
-> Integer
countNonCrossingPartitionsWithKParts :: Int -> Int -> Integer
countNonCrossingPartitionsWithKParts = Int -> Int -> Integer
countPeakingDyckPaths
randomNonCrossingPartition :: RandomGen g => Int -> g -> (NonCrossing,g)
randomNonCrossingPartition :: forall g. RandomGen g => Int -> g -> (NonCrossing, g)
randomNonCrossingPartition Int
n g
g0 = (LatticePath -> NonCrossing
dyckPathToNonCrossingPartition LatticePath
dyck, g
g1) where
(LatticePath
dyck,g
g1) = forall g. RandomGen g => Int -> g -> (LatticePath, g)
randomDyckPath Int
n g
g0