{-# LANGUAGE GADTs, UndecidableInstances #-}
module Distribution.Compat.Parsing
(
choice
, option
, optional
, skipOptional
, between
, some
, many
, sepBy
, sepBy1
, sepEndBy1
, sepEndBy
, endBy1
, endBy
, count
, chainl
, chainr
, chainl1
, chainr1
, manyTill
, Parsing(..)
) where
import Prelude ()
import Distribution.Compat.Prelude
import Control.Applicative ((<**>), optional)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.State.Lazy as Lazy
import Control.Monad.Trans.State.Strict as Strict
import Control.Monad.Trans.Writer.Lazy as Lazy
import Control.Monad.Trans.Writer.Strict as Strict
import Control.Monad.Trans.RWS.Lazy as Lazy
import Control.Monad.Trans.RWS.Strict as Strict
import Control.Monad.Trans.Reader (ReaderT (..))
import Control.Monad.Trans.Identity (IdentityT (..))
import Data.Foldable (asum)
import qualified Text.Parsec as Parsec
import qualified Distribution.Compat.ReadP as ReadP
choice :: Alternative m => [m a] -> m a
choice = asum
{-# INLINE choice #-}
option :: Alternative m => a -> m a -> m a
option x p = p <|> pure x
{-# INLINE option #-}
skipOptional :: Alternative m => m a -> m ()
skipOptional p = (() <$ p) <|> pure ()
{-# INLINE skipOptional #-}
between :: Applicative m => m bra -> m ket -> m a -> m a
between bra ket p = bra *> p <* ket
{-# INLINE between #-}
sepBy :: Alternative m => m a -> m sep -> m [a]
sepBy p sep = sepBy1 p sep <|> pure []
{-# INLINE sepBy #-}
sepBy1 :: Alternative m => m a -> m sep -> m [a]
sepBy1 p sep = (:) <$> p <*> many (sep *> p)
{-# INLINE sepBy1 #-}
sepEndBy1 :: Alternative m => m a -> m sep -> m [a]
sepEndBy1 p sep = (:) <$> p <*> ((sep *> sepEndBy p sep) <|> pure [])
sepEndBy :: Alternative m => m a -> m sep -> m [a]
sepEndBy p sep = sepEndBy1 p sep <|> pure []
{-# INLINE sepEndBy #-}
endBy1 :: Alternative m => m a -> m sep -> m [a]
endBy1 p sep = some (p <* sep)
{-# INLINE endBy1 #-}
endBy :: Alternative m => m a -> m sep -> m [a]
endBy p sep = many (p <* sep)
{-# INLINE endBy #-}
count :: Applicative m => Int -> m a -> m [a]
count n p | n <= 0 = pure []
| otherwise = sequenceA (replicate n p)
{-# INLINE count #-}
chainr :: Alternative m => m a -> m (a -> a -> a) -> a -> m a
chainr p op x = chainr1 p op <|> pure x
{-# INLINE chainr #-}
chainl :: Alternative m => m a -> m (a -> a -> a) -> a -> m a
chainl p op x = chainl1 p op <|> pure x
{-# INLINE chainl #-}
chainl1 :: Alternative m => m a -> m (a -> a -> a) -> m a
chainl1 p op = scan where
scan = p <**> rst
rst = (\f y g x -> g (f x y)) <$> op <*> p <*> rst <|> pure id
{-# INLINE chainl1 #-}
chainr1 :: Alternative m => m a -> m (a -> a -> a) -> m a
chainr1 p op = scan where
scan = p <**> rst
rst = (flip <$> op <*> scan) <|> pure id
{-# INLINE chainr1 #-}
manyTill :: Alternative m => m a -> m end -> m [a]
manyTill p end = go where go = ([] <$ end) <|> ((:) <$> p <*> go)
{-# INLINE manyTill #-}
infixr 0 <?>
class Alternative m => Parsing m where
try :: m a -> m a
(<?>) :: m a -> String -> m a
skipMany :: m a -> m ()
skipMany p = () <$ many p
{-# INLINE skipMany #-}
skipSome :: m a -> m ()
skipSome p = p *> skipMany p
{-# INLINE skipSome #-}
unexpected :: String -> m a
eof :: m ()
notFollowedBy :: Show a => m a -> m ()
instance (Parsing m, MonadPlus m) => Parsing (Lazy.StateT s m) where
try (Lazy.StateT m) = Lazy.StateT $ try . m
{-# INLINE try #-}
Lazy.StateT m <?> l = Lazy.StateT $ \s -> m s <?> l
{-# INLINE (<?>) #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (Lazy.StateT m) = Lazy.StateT
$ \s -> notFollowedBy (fst <$> m s) >> return ((),s)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m) => Parsing (Strict.StateT s m) where
try (Strict.StateT m) = Strict.StateT $ try . m
{-# INLINE try #-}
Strict.StateT m <?> l = Strict.StateT $ \s -> m s <?> l
{-# INLINE (<?>) #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (Strict.StateT m) = Strict.StateT
$ \s -> notFollowedBy (fst <$> m s) >> return ((),s)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m) => Parsing (ReaderT e m) where
try (ReaderT m) = ReaderT $ try . m
{-# INLINE try #-}
ReaderT m <?> l = ReaderT $ \e -> m e <?> l
{-# INLINE (<?>) #-}
skipMany (ReaderT m) = ReaderT $ skipMany . m
{-# INLINE skipMany #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (ReaderT m) = ReaderT $ notFollowedBy . m
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Strict.WriterT w m) where
try (Strict.WriterT m) = Strict.WriterT $ try m
{-# INLINE try #-}
Strict.WriterT m <?> l = Strict.WriterT (m <?> l)
{-# INLINE (<?>) #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (Strict.WriterT m) = Strict.WriterT
$ notFollowedBy (fst <$> m) >>= \x -> return (x, mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Lazy.WriterT w m) where
try (Lazy.WriterT m) = Lazy.WriterT $ try m
{-# INLINE try #-}
Lazy.WriterT m <?> l = Lazy.WriterT (m <?> l)
{-# INLINE (<?>) #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (Lazy.WriterT m) = Lazy.WriterT
$ notFollowedBy (fst <$> m) >>= \x -> return (x, mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Lazy.RWST r w s m) where
try (Lazy.RWST m) = Lazy.RWST $ \r s -> try (m r s)
{-# INLINE try #-}
Lazy.RWST m <?> l = Lazy.RWST $ \r s -> m r s <?> l
{-# INLINE (<?>) #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (Lazy.RWST m) = Lazy.RWST
$ \r s -> notFollowedBy ((\(a,_,_) -> a) <$> m r s) >>= \x -> return (x, s, mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, MonadPlus m, Monoid w) => Parsing (Strict.RWST r w s m) where
try (Strict.RWST m) = Strict.RWST $ \r s -> try (m r s)
{-# INLINE try #-}
Strict.RWST m <?> l = Strict.RWST $ \r s -> m r s <?> l
{-# INLINE (<?>) #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (Strict.RWST m) = Strict.RWST
$ \r s -> notFollowedBy ((\(a,_,_) -> a) <$> m r s) >>= \x -> return (x, s, mempty)
{-# INLINE notFollowedBy #-}
instance (Parsing m, Monad m) => Parsing (IdentityT m) where
try = IdentityT . try . runIdentityT
{-# INLINE try #-}
IdentityT m <?> l = IdentityT (m <?> l)
{-# INLINE (<?>) #-}
skipMany = IdentityT . skipMany . runIdentityT
{-# INLINE skipMany #-}
unexpected = lift . unexpected
{-# INLINE unexpected #-}
eof = lift eof
{-# INLINE eof #-}
notFollowedBy (IdentityT m) = IdentityT $ notFollowedBy m
{-# INLINE notFollowedBy #-}
instance (Parsec.Stream s m t, Show t) => Parsing (Parsec.ParsecT s u m) where
try = Parsec.try
(<?>) = (Parsec.<?>)
skipMany = Parsec.skipMany
skipSome = Parsec.skipMany1
unexpected = Parsec.unexpected
eof = Parsec.eof
notFollowedBy = Parsec.notFollowedBy
instance t ~ Char => Parsing (ReadP.Parser r t) where
try = id
(<?>) = const
skipMany = ReadP.skipMany
skipSome = ReadP.skipMany1
unexpected = const ReadP.pfail
eof = ReadP.eof
notFollowedBy p = ((Just <$> p) ReadP.+++ pure Nothing)
>>= maybe (pure ()) (unexpected . show)