module Sym.Perm.Class
(
inc
, dec
, av1
, av12
, av21
, av123
, av132
, av213
, av231
, av312
, av321
, av1243
, av1324
, av2134
, av
, vee
, caret
, gt
, lt
, wedges
, separables
, kLayered
, layered
, kFibonacci
, fibonacci
) where
import Sym.Internal.Util
import Sym.Perm
import Sym.Perm.Bijection
import Sym.Perm.Constructions
import Sym.Perm.Pattern
import qualified Sym.Perm.D8 as D8
inc :: Int -> [Perm]
inc = av21
dec :: Int -> [Perm]
dec = av12
av1 :: Int -> [Perm]
av1 0 = [emptyperm]
av1 _ = []
av12 :: Int -> [Perm]
av12 n = [ebb n]
av21 :: Int -> [Perm]
av21 n = [idperm n]
av123 :: Int -> [Perm]
av123 = map simionSchmidt' . av132
av132 :: Int -> [Perm]
av132 = map D8.reverse . av231
av213 :: Int -> [Perm]
av213 = map D8.complement . av231
av231 :: Int -> [Perm]
av231 0 = [emptyperm]
av231 n = do
k <- [0..n1]
s <- streamAv231 !! k
t <- streamAv231 !! (nk1)
return $ s /+/ (one \-\ t)
streamAv231 :: [[Perm]]
streamAv231 = map av231 [0..]
av312 :: Int -> [Perm]
av312 = map D8.inverse . av231
av321 :: Int -> [Perm]
av321 = map D8.complement . av123
av1243 :: Int -> [Perm]
av1243 n = avoiders [fromList [0,1,3,2]] (perms n)
av1324 :: Int -> [Perm]
av1324 n = avoiders [fromList [0,2,1,3]] (perms n)
av2134 :: Int -> [Perm]
av2134 n = avoiders [fromList [1,0,2,3]] (perms n)
av :: String -> Int -> [Perm]
av s = avoiders (map mkPerm (words s)) . perms
vee :: Int -> [Perm]
vee = (streamVee !!)
streamVee :: [[Perm]]
streamVee = [emptyperm] : [one] : zipWith (++) vee_n n_vee
where
n_vee = (map.map) (one \-\) ws
vee_n = (map.map) (/+/ one) ws
ws = tail streamVee
caret :: Int -> [Perm]
caret = map D8.complement . vee
gt :: Int -> [Perm]
gt = map D8.rotate . vee
lt :: Int -> [Perm]
lt = map D8.reverse . gt
union :: [Int -> [Perm]] -> Int -> [Perm]
union cs n = nubSort $ concat [ c n | c <- cs ]
wedges :: Int -> [Perm]
wedges = union [vee, caret, gt, lt]
compositions :: Int -> Int -> [[Int]]
compositions 0 0 = [[]]
compositions 0 _ = []
compositions _ 0 = []
compositions k n = [1..n] >>= \i -> map (i:) (compositions (k1) (ni))
boundedCompositions :: Int -> Int -> Int -> [[Int]]
boundedCompositions _ 0 0 = [[]]
boundedCompositions _ 0 _ = []
boundedCompositions _ _ 0 = []
boundedCompositions b k n = [1..b] >>= \i -> map (i:) (boundedCompositions b (k1) (ni))
separables :: Int -> [Perm]
separables 0 = [emptyperm]
separables 1 = [one]
separables n = pIndec n ++ mIndec n
where
comps m = [2..m] >>= \k -> compositions k m
pIndec 0 = []
pIndec 1 = [one]
pIndec m = comps m >>= map skewSum . mapM (streamMIndec !!)
mIndec m = map D8.complement $ pIndec m
streamMIndec = map mIndec [0..]
kLayered :: Int -> Int -> [Perm]
kLayered k = map (directSum . map ebb) . compositions k
layered :: Int -> [Perm]
layered n = [1..n] >>= flip kLayered n
kFibonacci :: Int -> Int -> [Perm]
kFibonacci k = map (directSum . map ebb) . boundedCompositions 2 k
fibonacci :: Int -> [Perm]
fibonacci n = [1..n] >>= flip kFibonacci n