{-# 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 (Eq,Ord,Show,Read)
_isNonCrossing :: [[Int]] -> Bool
_isNonCrossing zzs0 = _isNonCrossingUnsafe (_standardizeNonCrossing zzs0)
_isNonCrossingUnsafe :: [[Int]] -> Bool
_isNonCrossingUnsafe zzs =
case _nonCrossingPartitionToDyckPathMaybe zzs of
Nothing -> False
Just dyck -> case dyckPathToNonCrossingPartitionMaybe dyck of
Nothing -> False
Just (NonCrossing yys) -> yys == zzs
_standardizeNonCrossing :: [[Int]] -> [[Int]]
_standardizeNonCrossing = sortBy (comparing myhead) . map reverseSort where
myhead xs = case xs of
(x:xs) -> x
[] -> error "_standardizeNonCrossing: empty subset"
fromNonCrossing :: NonCrossing -> [[Int]]
fromNonCrossing (NonCrossing xs) = xs
toNonCrossingUnsafe :: [[Int]] -> NonCrossing
toNonCrossingUnsafe = NonCrossing
toNonCrossing :: [[Int]] -> NonCrossing
toNonCrossing xxs = case toNonCrossingMaybe xxs of
Just nc -> nc
Nothing -> error "toNonCrossing: not a non-crossing partition"
toNonCrossingMaybe :: [[Int]] -> Maybe NonCrossing
toNonCrossingMaybe xxs0 =
if _isNonCrossingUnsafe xxs
then Just $ NonCrossing xxs
else Nothing
where
xxs = _standardizeNonCrossing xxs0
setPartitionToNonCrossing :: SetPartition -> Maybe NonCrossing
setPartitionToNonCrossing (SetPartition zzs0) =
if _isNonCrossingUnsafe zzs
then Just $ NonCrossing zzs
else Nothing
where
zzs = _standardizeNonCrossing zzs0
instance HasNumberOfParts NonCrossing where
numberOfParts (NonCrossing p) = length p
dyckPathToNonCrossingPartition :: LatticePath -> NonCrossing
dyckPathToNonCrossingPartition = NonCrossing . go 0 [] [] [] where
go :: Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> [[Int]]
go !cnt stack small big path =
case path of
(x:xs) -> case x of
UpStep -> let cnt' = cnt + 1 in case xs of
(y:ys) -> case y of
UpStep -> go cnt' (cnt':stack) small big xs
DownStep -> go cnt' (cnt':stack) [] (reverse small : big) xs
[] -> error "dyckPathToNonCrossingPartition: last step is an UpStep (thus input was not a Dyck path)"
DownStep -> case stack of
(k:ks) -> go cnt ks (k:small) big xs
[] -> error "dyckPathToNonCrossingPartition: empty stack, shouldn't happen (thus input was not a Dyck path)"
[] -> tail $ reverse (reverse small : big)
dyckPathToNonCrossingPartitionMaybe :: LatticePath -> Maybe NonCrossing
dyckPathToNonCrossingPartitionMaybe = fmap NonCrossing . go 0 [] [] [] where
go :: Int -> [Int] -> [Int] -> [[Int]] -> LatticePath -> Maybe [[Int]]
go !cnt stack small big path =
case path of
(x:xs) -> case x of
UpStep -> let cnt' = cnt + 1 in case xs of
(y:ys) -> case y of
UpStep -> go cnt' (cnt':stack) small big xs
DownStep -> go cnt' (cnt':stack) [] (reverse small : big) xs
[] -> Nothing
DownStep -> case stack of
(k:ks) -> go cnt ks (k:small) big xs
[] -> Nothing
[] -> Just $ tail $ reverse (reverse small : big)
nonCrossingPartitionToDyckPath :: NonCrossing -> LatticePath
nonCrossingPartitionToDyckPath (NonCrossing zzs) = go 0 zzs where
go !k (ys@(y:_):yys) = replicate (y-k) UpStep ++ replicate (length ys) DownStep ++ go y yys
go !k [] = []
go _ _ = error "nonCrossingPartitionToDyckPath: shouldnt't happen"
_nonCrossingPartitionToDyckPathMaybe :: [[Int]] -> Maybe LatticePath
_nonCrossingPartitionToDyckPathMaybe = go 0 where
go !k (ys@(y:_):yys) = fmap (\zs -> replicate (y-k) UpStep ++ replicate (length ys) DownStep ++ zs) (go y yys)
go !k [] = Just []
go _ _ = Nothing
nonCrossingPartitions :: Int -> [NonCrossing]
nonCrossingPartitions = map dyckPathToNonCrossingPartition . dyckPaths
nonCrossingPartitionsWithKParts
:: Int
-> Int
-> [NonCrossing]
nonCrossingPartitionsWithKParts k n = map dyckPathToNonCrossingPartition $ peakingDyckPaths k n
countNonCrossingPartitions :: Int -> Integer
countNonCrossingPartitions = countDyckPaths
countNonCrossingPartitionsWithKParts
:: Int
-> Int
-> Integer
countNonCrossingPartitionsWithKParts = countPeakingDyckPaths
randomNonCrossingPartition :: RandomGen g => Int -> g -> (NonCrossing,g)
randomNonCrossingPartition n g0 = (dyckPathToNonCrossingPartition dyck, g1) where
(dyck,g1) = randomDyckPath n g0