module Math.Sym.Class
(
inc, dec
, av123, av132, av213, av231, av312, av321
, vee, caret, gt, lt, wedges, separables
) where
import Math.Sym (Perm, empty, one, idperm, (/+/), (\-\), ssum, normalize)
import Math.Sym.Bijection (simionSchmidt')
import qualified Math.Sym.D8 as D8
inc :: Perm a => Int -> [a]
inc n = [idperm n]
dec :: Perm a => Int -> [a]
dec n = [D8.complement (idperm n)]
av123 :: Perm a => Int -> [a]
av123 = map simionSchmidt' . av132
av132 :: Perm a => Int -> [a]
av132 = map D8.reverse . av231
av213 :: Perm a => Int -> [a]
av213 = map D8.complement . av231
av231 :: Perm a => Int -> [a]
av231 0 = [empty]
av231 n = do
k <- [0..n1]
s <- streamAv231 !! k
t <- streamAv231 !! (nk1)
return $ s /+/ (one \-\ t)
streamAv231 :: Perm a => [[a]]
streamAv231 = map av231 [0..]
av312 :: Perm a => Int -> [a]
av312 = map D8.reverse . av213
av321 :: Perm a => Int -> [a]
av321 = map D8.complement . av123
vee :: Perm a => Int -> [a]
vee = (streamVee !!)
streamVee :: Perm a => [[a]]
streamVee = [empty] : [one] : zipWith (++) vee_n n_vee
where
n_vee = (map.map) (one \-\) ws
vee_n = (map.map) (/+/ one) ws
ws = tail streamVee
caret :: Perm a => Int -> [a]
caret = map D8.complement . vee
gt :: Perm a => Int -> [a]
gt = map D8.rotate . vee
lt :: Perm a => Int -> [a]
lt = map D8.reverse . gt
union :: Perm a => [Int -> [a]] -> Int -> [a]
union cs n = normalize $ concat [ c n | c <- cs ]
wedges :: Perm a => Int -> [a]
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))
separables :: Perm a => Int -> [a]
separables 0 = [empty]
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 ssum . mapM (streamMIndec !!)
mIndec m = map D8.complement $ pIndec m
streamMIndec = map mIndec [0..]