module Math.Spe
(
Spe
, (.+.), assemble, (.*.), (<*.), prod, ordProd, (.^), (<^), (><), o
, dx, pointed, ofSize, nonEmpty
, set, one, x, kBal, bal, par, kList, list, cyc, perm, kSubset, subset
) where
import Control.Applicative
infixl 6 .+.
infixl 7 .*.
infixl 7 <*.
infixr 8 .^
infixr 8 <^
type Spe a c = [a] -> [c]
type Bipartition a = [a] -> [([a], [a])]
(.+.) :: Spe a b -> Spe a c -> Spe a (Either b c)
(.+.) f g xs = (Left <$> f xs) ++ (Right <$> g xs)
assemble :: [Spe a c] -> Spe a c
assemble fs xs = fs >>= \f -> f xs
kEndBy :: Bipartition a -> Int -> [a] -> [[[a]]]
kEndBy _ 0 [] = [[]]
kEndBy _ 0 _ = []
kEndBy h k xs = h xs >>= \(b,ys) -> (b:) <$> kEndBy h (k1) ys
bipartL :: Bipartition a
bipartL [] = [([], [])]
bipartL xs@(x:xt) = ([], xs) : [ (x:ys, zs) | (ys,zs) <- bipartL xt ]
bipartB :: Bipartition a
bipartB [] = [([], [])]
bipartB (x:xs) = bipartB xs >>= \(ys, zs) -> [(x:ys, zs), (ys, x:zs)]
mulBy :: Bipartition a -> Spe a b -> Spe a c -> Spe a (b,c)
mulBy h f g xs = h xs >>= \(ys,zs) -> (,) <$> f ys <*> g zs
(.*.) :: Spe a b -> Spe a c -> Spe a (b, c)
(.*.) = mulBy bipartB
(<*.) :: Spe a b -> Spe a c -> Spe a (b, c)
(<*.) = mulBy bipartL
prodBy :: Bipartition a -> [Spe a b] -> Spe a [b]
prodBy h fs xs = zipWith ($) fs <$> kEndBy h (length fs) xs >>= sequence
prod :: [Spe a b] -> Spe a [b]
prod = prodBy bipartB
ordProd :: [Spe a b] -> Spe a [b]
ordProd = prodBy bipartL
powerBy :: Bipartition a -> Spe a b -> Int -> Spe a [b]
powerBy h f k = prodBy h $ replicate k f
(.^) :: Spe a b -> Int -> Spe a [b]
(.^) = powerBy bipartB
(<^) :: Spe a b -> Int -> Spe a [b]
(<^) = powerBy bipartL
(><) :: Spe a b -> Spe a c -> Spe a (b,c)
(><) f g xs = (,) <$> f xs <*> g xs
o :: Spe [a] b -> Spe a c -> Spe a (b, [c])
o f g xs = par xs >>= f >< mapM g
dx :: Spe (Maybe a) b -> Spe a b
dx f xs = f $ Nothing : (Just <$> xs)
pointed :: Spe a b -> Spe a (b, a)
pointed f = f >< id
isOfLength :: [a] -> Int -> Bool
[] `isOfLength` n = n == 0
(_:xs) `isOfLength` n = n > 0 && xs `isOfLength` (n1)
ofSize :: Spe a c -> Int -> Spe a c
(f `ofSize` n) xs | xs `isOfLength` n = f xs
| otherwise = []
nonEmpty :: Spe a c -> Spe a c
nonEmpty _ [] = []
nonEmpty f xs = f xs
set :: Spe a [a]
set = return
one :: Spe a ()
one xs = [ () | null xs ]
x :: Spe a a
x = id `ofSize` 1
kBal :: Int -> Spe a [[a]]
kBal k = nonEmpty set .^ k
bal :: Spe a [[a]]
bal [] = [[]]
bal xs = [ b:bs | (b, ys) <- init (bipartB xs), bs <- bal ys ]
par :: Spe a [[a]]
par [] = [[]]
par (x:xs) = [ (x:b) : bs | (b, ys) <- bipartB xs, bs <- par ys ]
kList :: Int -> Spe a [a]
kList k = x .^ k
list :: Spe a [a]
list xs = kList (length xs) xs
cyc :: Spe a [a]
cyc [] = []
cyc (x:xs) = (x:) <$> list xs
perm :: Spe a [[a]]
perm = map fst . (set `o` cyc)
kSubset :: Int -> Spe a [a]
kSubset k = map fst . (set `ofSize` k .*. set)
subset :: Spe a [a]
subset = map fst . bipartB