-- | A collection of predefined combinators. Use these to combine other parsers -- into more complex ones. module Text.Parcom.Combinators ( choice, namedChoice , before, between , many, many1, manySepBy , times , skip , possibly, optional, option ) where import Text.Parcom.Core import Text.Parcom.Internal import Control.Monad (liftM) import Data.Maybe (fromMaybe) -- | Walk a list of options, return the first one that succeeds. choice :: (Monad m, Stream s t) => [ParcomT s t m a] -> ParcomT s t m a choice xs = foldl (<|>) empty xs "I tried to make a choice, but couldn't" -- | Like 'choice', but each choice tagged with a human-readable name for -- better error reporting. namedChoice :: (Monad m, Stream s t) => [(String, ParcomT s t m a)] -> ParcomT s t m a namedChoice xs = choice (map snd xs) (formatOptionList . map fst) xs -- | Match two consecutive parser, return the first parser's result iff both -- succeed. before :: (Monad m, Stream s t) => ParcomT s t m a -> ParcomT s t m b -> ParcomT s t m a before p q = do { v <- p; q; return v } -- | Match three consecutive parsers, return the middle parser's result iff -- all three match. Parsers are given in the order inner, left, right. between :: (Monad m, Stream s t) => ParcomT s t m a -> ParcomT s t m l -> ParcomT s t m r -> ParcomT s t m a between p l r = do { l; v <- p; r; return v } -- | Match zero or more occurrences of a parser many :: (Monad m, Stream s t) => ParcomT s t m a -> ParcomT s t m [a] many p = handle p f m where f e = return [] m x = do xs <- many p return (x:xs) -- | Match one or more occurrences of a parser many1 :: (Monad m, Stream s t) => ParcomT s t m a -> ParcomT s t m [a] many1 p = do xs <- many p if null xs then fail "Expected at least one item" else return xs -- | Given an item parser and a separator parser, keep parsing until the -- separator or the item fails. manySepBy :: (Monad m, Stream s t) => ParcomT s t m a -> ParcomT s t m b -> ParcomT s t m [a] manySepBy p s = go where go = do -- try an item handle p f m where -- item does not parse: return empty list (no matches) f e = return [] -- item does parse: keep the item, try the separator. m x = handle s -- separator does not parse: return the one item we have (\e -> return [x]) -- separator does parse: recurse and prepend our item (\_ -> go >>= \xs -> return (x:xs)) -- | Run the given parser n times, returning all the results as a list. times :: (Monad m, Stream s t) => Int -> ParcomT s t m a -> ParcomT s t m [a] times 0 p = return [] times n p = do x <- p xs <- times (n - 1) p return (x:xs) -- | Ignore the result of a parser. skip :: Monad m => ParcomT s t m a -> ParcomT s t m () skip p = p >> return () -- | Optional parsing to Maybe possibly :: Monad m => ParcomT s t m a -> ParcomT s t m (Maybe a) possibly p = Just `liftM` p <|> return Nothing -- | Optional parsing with default optional :: Monad m => a -> ParcomT s t m a -> ParcomT s t m a optional d p = fromMaybe d `liftM` possibly p -- | Optional parsing, ignoring (but consuming) result option :: Monad m => ParcomT s t m a -> ParcomT s t m () option p = skip $ optional undefined p