{-# LANGUAGE LambdaCase #-} {-# LANGUAGE TupleSections #-} -- | Extend a monad with the ability to parse symbol sequences module Mini.Transformers.ParserT ( -- * Types ParserT ( ParserT ), ParseError ( ParseError, unexpected ), -- * Runner runParserT, -- * Parsers sat, item, symbol, string, oneOf, noneOf, eof, peek, -- * Combinators sepBy, sepBy1, till, chainl1, chainr1, between, option, reject, accept, findFirst, findLast, annotate, ) where import Control.Applicative ( Alternative, empty, many, (<|>), ) import Control.Monad ( ap, liftM, (>=>), ) import Control.Monad.IO.Class ( MonadIO, liftIO, ) import Data.Bool ( bool, ) import Mini.Transformers.Class ( MonadTrans, lift, ) import Prelude ( Applicative, Bool ( True ), Either ( Left, Right ), Eq, Foldable, Functor, Monad, MonadFail, Monoid, Semigroup, Show, String, Traversable, const, either, elem, fail, flip, fmap, fst, mempty, notElem, pure, show, traverse, ($), (*>), (.), (<$), (<$>), (<*), (<*>), (<>), (==), (>>=), ) {- - Types -} -- | A transformer parsing symbols /s/, inner monad /m/, return /a/ newtype ParserT s m a = ParserT { runParserT :: [s] -> m (Either ParseError (a, [s])) -- ^ Unwrap a 'ParserT' computation with a sequence of symbols to parse } instance (Monad m) => Functor (ParserT s m) where fmap = liftM instance (Monad m) => Applicative (ParserT s m) where pure a = ParserT $ pure . Right . (a,) (<*>) = ap -- | Parse @p@ or, if @p@ fails, backtrack and parse @q@ via @p \<|\> q@ instance (Monad m, Eq s) => Alternative (ParserT s m) where empty = fail empty m <|> n = ParserT $ \ss -> runParserT m ss >>= either (const $ runParserT n ss) (pure . Right) instance (Monad m) => Monad (ParserT s m) where m >>= k = ParserT $ runParserT m >=> either (pure . Left) (\(a, ss') -> runParserT (k a) ss') instance MonadTrans (ParserT s) where lift m = ParserT $ \ss -> Right . (,ss) <$> m -- | Combine the results of @p@ and @q@ via @p <> q@ instance (Monad m, Semigroup a) => Semigroup (ParserT s m a) where m <> n = (<>) <$> m <*> n instance (Monad m, Monoid a) => Monoid (ParserT s m a) where mempty = pure mempty instance (Monad m) => MonadFail (ParserT s m) where fail = ParserT . const . pure . Left . ParseError instance (MonadIO m) => MonadIO (ParserT s m) where liftIO = lift . liftIO -- | A parse error newtype ParseError = ParseError {unexpected :: String} deriving (Show) {- - Parsers -} -- | Parse symbols satisfying a predicate sat :: (Applicative m, Show s) => (s -> Bool) -> ParserT s m s sat p = ParserT $ \case [] -> pure . Left $ ParseError [] (s : ss) -> bool (pure . Left . ParseError $ show s) (pure $ Right (s, ss)) $ p s -- | Parse any symbol item :: (Applicative m, Show s) => ParserT s m s item = sat $ const True -- | Parse a symbol symbol :: (Applicative m, Show s, Eq s) => s -> ParserT s m s symbol = sat . (==) -- | Parse a sequence of symbols string :: (Monad m, Traversable t, Show s, Eq s) => t s -> ParserT s m (t s) string = traverse symbol -- | Parse symbols included in a collection oneOf :: (Applicative m, Foldable t, Show s, Eq s) => t s -> ParserT s m s oneOf = sat . flip elem -- | Parse symbols excluded from a collection noneOf :: (Applicative m, Foldable t, Show s, Eq s) => t s -> ParserT s m s noneOf = sat . flip notElem -- | Parse successfully only at end of input eof :: (Monad m, Show s) => ParserT s m () eof = reject item -- | Parse the next symbol without consuming it peek :: (Monad m, Show s) => ParserT s m s peek = accept item {- - Combinators -} -- | Parse zero or more @p@ separated by @q@ via @p \`sepBy\` q@ sepBy :: (Monad m, Eq s) => ParserT s m a -> ParserT s m b -> ParserT s m [a] sepBy p = option [] . sepBy1 p -- | Parse one or more @p@ separated by @q@ via @p \`sepBy1\` q@ sepBy1 :: (Monad m, Eq s) => ParserT s m a -> ParserT s m b -> ParserT s m [a] sepBy1 p sep = (:) <$> p <*> many (sep *> p) -- | Parse zero or more @p@ until @q@ succeeds via @p \`till\` q@ till :: (Monad m, Eq s) => ParserT s m a -> ParserT s m b -> ParserT s m [a] till p end = ([] <$ end) <|> ((:) <$> p <*> till p end) -- | Parse one or more @p@ left-associatively chained by @f@ via @chainl1 p f@ chainl1 :: (Monad m, Eq s) => ParserT s m a -> ParserT s m (a -> a -> a) -> ParserT s m a chainl1 p f = p >>= go where go a = option a $ f <*> pure a <*> p >>= go -- | Parse one or more @p@ right-associatively chained by @f@ via @chainr1 p f@ chainr1 :: (Monad m, Eq s) => ParserT s m a -> ParserT s m (a -> a -> a) -> ParserT s m a chainr1 p f = go where go = p >>= rest rest a = option a $ f <*> pure a <*> go >>= rest -- | Parse @p@ enclosed by @a@ and @b@ via @between a b p@ between :: (Monad m) => ParserT s m open -> ParserT s m close -> ParserT s m a -> ParserT s m a between open close p = open *> p <* close -- | Parse @p@ returning @a@ in case of failure via @option a p@ option :: (Monad m, Eq s) => a -> ParserT s m a -> ParserT s m a option a p = p <|> pure a -- | Parse @p@, without consuming input, iff @p@ fails via @reject p@ reject :: (Monad m, Show a) => ParserT s m a -> ParserT s m () reject p = ParserT $ \ss -> runParserT p ss >>= either (const . pure $ Right ((), ss)) (pure . Left . ParseError . show . fst) -- | Parse @p@, without consuming input, iff @p@ succeeds via @accept p@ accept :: (Monad m) => ParserT s m a -> ParserT s m a accept p = ParserT $ \ss -> runParserT p ss >>= either (pure . Left) (pure . Right . (,ss) . fst) -- | Find and parse the first instance of @p@ via @findFirst p@ findFirst :: (Monad m, Eq s, Show s) => ParserT s m a -> ParserT s m a findFirst p = p <|> (item *> findFirst p) -- | Find and parse the last instance of @p@ via @findLast p@ findLast :: (Monad m, Eq s, Show s) => ParserT s m a -> ParserT s m a findLast p = findFirst p >>= flip option (findLast p) -- | Prepend an error message to that of a parser annotate :: (Monad m) => String -> ParserT s m a -> ParserT s m a annotate s p = ParserT $ runParserT p >=> either (pure . Left . ParseError . (s <>) . unexpected) (pure . Right)