-- | Primitive parsers. -- -- Regarding consuming input, unless states otherwise, all of these behave as -- follows: -- -- * If a parser succeeds, it consumes the input it matches -- -- * If a parser fails, it does not consume any input at all module Text.Parcom.Prim ( anyToken, oneOf, noneOf, eof , satisfy , token, tokens, prefix ) where import Text.Parcom.Core import Text.Parcom.Internal import Text.Parcom.Stream (toList, fromList) import Control.Monad (liftM) -- | Gets the next token from the stream anyToken :: (Monad m, Stream s t, Token t) => ParcomT s t m t anyToken = next -- | Succeeds iff end-of-input has been reached eof :: (Monad m, Stream s t, Token t) => ParcomT s t m () eof = notFollowedBy anyToken "end of input" -- | Matches one token against a list of possible tokens; returns the -- matching token or fails. oneOf :: (Monad m, Stream s t, Token t, Show t, Eq t) => [t] -> ParcomT s t m t oneOf xs = satisfy (`elem` xs) (formatOptionList . map show) xs -- | Matches one token against a list of prohibited tokens; returns the -- non-matching token or fails. noneOf :: (Monad m, Stream s t, Token t, Show t, Eq t) => [t] -> ParcomT s t m t noneOf xs = satisfy (not . (`elem` xs)) "anything but " ++ (formatOptionList . map show) xs -- | Succeeds if the given predicate is met for the next token. satisfy :: (Monad m, Stream s t, Token t) => (t -> Bool) -> ParcomT s t m t satisfy p = do c <- peek if p c then next else fail "Predicate not met" -- | Exactly match one particular token token :: (Monad m, Stream s t, Token t, Show t, Eq t) => t -> ParcomT s t m t token t = satisfy (== t) show t -- | Match a series of tokens exactly tokens :: (Monad m, Stream s t, Token t, Eq t, Show t) => [t] -> ParcomT s t m [t] tokens [] = return [] tokens (x:xs) = do c <- token x cs <- tokens xs return (c:cs) -- | Match a series of tokens exactly. Unlike 'tokens', this parser accepts -- the target sequence by the stream's type instead of list-of-tokens. -- Depending on the stream's 'Listish' implementation, this may be more -- efficient than matching and consuming the tokens one-by-one, as 'tokens' -- does. prefix :: (Monad m, Stream s t, Token t, Eq t, Show t, Listish s t) => s -> ParcomT s t m s prefix str = fromList `liftM` tokens (toList str)