module Control.Applicative.Interleaved
(
Splittable (..),
Gram (..),
Alt (..),
mkG,
mkP,
(<<||>),
(<||>),
sepBy,
gmList,
module Control.Applicative,
module Data.Monoid
) where
import Control.Applicative
import Data.Monoid
infixl 4 <||>
infixl 4 <<||>
data Gram f a = Gram [Alt f a] (Maybe a)
data Alt f a = forall b . Seq (f (b -> a)) (Gram f b)
| forall b. Bind (f b) (b -> Gram f a)
class Splittable f where
getNonPure :: f a -> Maybe (f a)
getPure :: f a -> Maybe a
instance Functor f => Monoid (Gram f (r -> r)) where
mappend p q = (.) <$> p <||> q
mempty = empty
instance (Show a) => Show (Gram f a) where
show (Gram l ma) = "Gram " ++ show (length l) ++ " " ++ show ma
mkG:: (Splittable f, Functor f) => f a -> Gram f a
mkG p = Gram (maybe [] (\p -> [(const <$> p) `Seq` pure ()]) (getNonPure p))
(getPure p)
instance Functor f => Functor (Gram f) where
fmap f (Gram alts e) = Gram (map (f <$>) alts) (f <$> e)
instance Functor f => Functor (Alt f) where
fmap a2c (fb2a `Seq` gb) = ((a2c.) <$> fb2a) `Seq` gb
fmap a2c (fb `Bind` b2ga) = fb `Bind` (\b -> fmap a2c (b2ga b))
(<<||>):: Functor f => Gram f (b->a) -> Gram f b -> Gram f a
gb2a@(Gram lb2a eb2a) <<||> ~gb@(Gram _ eb)
= Gram ( map (`fwdby` gb) lb2a) (eb2a <*> eb)
where (fc2b2a `Seq` gc) `fwdby` gb = (uncurry <$> fc2b2a) `Seq` ((,) <$> gc <||> gb)
(fc `Bind` c2gb2a) `fwdby` gb = fc `Bind` (\ c -> c2gb2a c <||> gb)
fb2a <||> fb = fb2a <<||> fb <|> flip ($) <$> fb <<||> fb2a
instance Functor f => Applicative (Gram f) where
pure a = Gram [] (Just a)
Gram lb2a mb2a <*> ~gb@(Gram lb mb)
= Gram (map (`fwdby` gb) lb2a ++ [b2a <$> fb | Just b2a <- [mb2a], fb <- lb]) (mb2a <*> mb)
where (fc2b2a `Seq` gc) `fwdby` gb = (uncurry <$> fc2b2a) `Seq` ((,) <$> gc <*> gb)
(fc `Bind` c2gb2a) `fwdby` gb = fc `Bind` (\b -> c2gb2a b <*> gb)
instance Functor f => Alternative (Gram f) where
empty = Gram [] Nothing
Gram ps pe <|> Gram qs qe = Gram (ps++qs) (pe <|> qe)
instance Functor f => Monad (Gram f) where
return a = Gram [] (Just a)
Gram lb mb >>= b2g_a =
let bindto :: Functor f => Alt f b -> (b -> Gram f a) -> Alt f a
(f_c2b `Seq` g_c) `bindto` b2g_a = f_c2b `Bind` \ c2b -> c2b <$> g_c >>= b2g_a
(f_c `Bind` c2g_b) `bindto` b2g_a = f_c `Bind` \ c -> c2g_b c >>= b2g_a
la = map (`bindto` b2g_a) lb
in case mb of
Nothing -> Gram la Nothing
Just b -> let Gram lra ma = b2g_a b
in Gram (la ++ lra) ma
mkP :: (Monad f, Applicative f, Alternative f) => Gram f a -> f a
mkP (Gram l_a m_a) = foldr (<|>) (maybe empty pure m_a)
(map mkP_Alt l_a)
where mkP_Alt (f_b2a `Seq` g_b ) = f_b2a <*> mkP g_b
mkP_Alt (f_b `Bind` b2g_a) = f_b >>= (mkP . b2g_a)
sepBy :: (Monad f, Applicative f, Alternative f) => Gram f a -> f b -> f a
sepBy g sep = mkP (insertSep sep g)
insertSep :: (Applicative f) => f b -> Gram f a -> Gram f a
insertSep sep (Gram na ea :: Gram f a) = Gram (map insertSepInAlt na) ea
where insertSepInAlt (fb2a `Seq` gb ) = fb2a `Seq` prefixSepInGram gb
insertSepInAlt (fc `Bind` c2ga) = fc `Bind` (insertSep sep . c2ga)
prefixSepInGram (Gram na ne) = Gram (map prefixSepInAlt na) ne
prefixSepInAlt :: Alt f b -> Alt f b
prefixSepInAlt (fb2a `Seq` gb) = (sep *> fb2a) `Seq` prefixSepInGram gb
gmList :: Functor f => Gram f a -> Gram f [a]
gmList p = let pm = ( (:) <$> p <<||> pm ) <|> pure [] in pm