module Control.Applicative.Permute
( Effects, perms
, once, opt, atLeast, between, exactly, many, some
) where
import Prelude hiding (length, sequence)
import Control.Applicative hiding (some, many)
import Data.Foldable
data Effects f a where
Nil :: a -> Effects f a
(:-) :: Freq f b -> Effects f (b -> a) -> Effects f a
infixr 5 :-
data Freq f a where
Once :: f a -> Freq f a
Opt :: f a -> Freq f (Maybe a)
AtLeast :: Int -> f a -> Freq f [a]
Between :: Int -> Int -> f a -> Freq f [a]
instance Functor (Effects f) where
fmap f (Nil x) = Nil (f x)
fmap f (p :- ps) = p :- fmap (fmap f) ps
instance Applicative (Effects f) where
pure = Nil
Nil g <*> y = fmap g y
(f :- x) <*> y = f :- (flip <$> x <*> y)
length :: Effects f a -> Int
length (Nil _) = 0
length (_ :- xs) = 1 + length xs
runFreq :: Alternative f => Freq f a -> f a
runFreq freq =
case freq of
Once p -> p
Opt p -> Just <$> p <|> pure Nothing
AtLeast 0 _ -> pure []
AtLeast n p -> (:) <$> p <*> runFreq (AtLeast (n 1) p)
Between 0 0 _ -> pure []
Between 0 m p -> runFreq (Between 0 (m 1) p) <|> pure []
Between n m p -> (:) <$> p <*> runFreq (Between (n 1) (m 1) p)
freqMatchesEpsilon :: Freq f a -> Maybe a
freqMatchesEpsilon freq =
case freq of
Opt _ -> Just Nothing
AtLeast 0 _ -> Just []
Between 0 _ _ -> Just []
_ -> Nothing
effectsMatchEpsilon :: Effects f a -> Maybe a
effectsMatchEpsilon eff =
case eff of
Nil x -> Just x
freq :- ps -> freqMatchesEpsilon freq <**> effectsMatchEpsilon ps
split :: Freq f a -> Effects f a
split freq =
case freq of
Once f -> once f
Opt f -> Just <$> once f
AtLeast n f -> (:) <$> once f <*> atLeast (0 `max` (n 1)) f
Between _ 1 f -> (:[]) <$> once f
Between n m f -> (:) <$> once f <*> between (0 `max` (n 1)) (m 1) f
lift :: Freq f a -> Effects f a
lift freq = freq :- Nil id
once :: f a -> Effects f a
once = lift . Once
opt :: f a -> Effects f (Maybe a)
opt = lift . Opt
atLeast :: Int -> f a -> Effects f [a]
atLeast n = lift . AtLeast n
between :: Int -> Int -> f a -> Effects f [a]
between n m = lift . Between n m
exactly :: Int -> f a -> Effects f [a]
exactly n = between n n
many :: f a -> Effects f [a]
many = atLeast 0
some :: f a -> Effects f [a]
some = atLeast 1
runEffects :: Alternative f => Effects f a -> f a
runEffects (Nil x) = pure x
runEffects (freq :- ps) = runFreq freq <**> runEffects ps
perms :: forall f a. Alternative f => Effects f a -> f a
perms (Nil x) = pure x
perms ps = asum . eps . map (permTail . splitHead) . firsts $ ps
where
permTail :: Effects f a -> f a
permTail (p :- ps') = runFreq p <**> perms ps'
permTail _ = undefined
eps :: [f a] -> [f a]
eps =
case effectsMatchEpsilon ps of
Just x -> (++ [pure x])
Nothing -> id
splitHead :: Effects f a -> Effects f a
splitHead (p :- ps') = split p <**> ps'
splitHead _ = undefined
firsts :: Effects f a -> [Effects f a]
firsts (Nil _) = []
firsts (freq :- ps) =
(freq :- ps) : map (\ps' -> swap (freq :- ps')) (firsts ps)
swap :: Effects f a -> Effects f a
swap (p0 :- p1 :- ps) = p1 :- p0 :- fmap flip ps
swap ps = ps