{-# LANGUAGE BangPatterns, CPP #-} -- | -- Module : Data.Attoparsec.Combinator -- Copyright : Daan Leijen 1999-2001, Bryan O'Sullivan 2009-2010 -- License : BSD3 -- -- Maintainer : bos@serpentine.com -- Stability : experimental -- Portability : portable -- -- Useful parser combinators, similar to those provided by Parsec. module Data.Attoparsec.Combinator ( choice , count , option , many1 , manyTill , sepBy , sepBy1 , skipMany , skipMany1 , eitherP -- * Inlined implementations of existing functions -- -- These are exact duplicates of functions already exported by the -- 'Control.Applicative' module, but whose definitions are -- inlined. In many cases, this leads to 2x performance -- improvements. , many ) where import Control.Applicative (Alternative, Applicative(..), empty, liftA2, (<|>), (*>), (<$>)) -- | @choice ps@ tries to apply the actions in the list @ps@ in order, -- until one of them succeeds. Returns the value of the succeeding -- action. choice :: Alternative f => [f a] -> f a choice = foldr (<|>) empty -- | @option x p@ tries to apply action @p@. If @p@ fails without -- consuming input, it returns the value @x@, otherwise the value -- returned by @p@. -- -- > priority = option 0 (digitToInt <$> digit) option :: Alternative f => a -> f a -> f a option x p = p <|> pure x -- | @many1 p@ applies the action @p@ /one/ or more times. Returns a -- list of the returned values of @p@. -- -- > word = many1 letter many1 :: Alternative f => f a -> f [a] many1 p = liftA2 (:) p (many p) {-# INLINE many1 #-} -- | @sepBy p sep@ applies /zero/ or more occurrences of @p@, separated -- by @sep@. Returns a list of the values returned by @p@. -- -- > commaSep p = p `sepBy` (symbol ",") sepBy :: Alternative f => f a -> f s -> f [a] sepBy p s = liftA2 (:) p ((s *> sepBy1 p s) <|> pure []) <|> pure [] -- | @sepBy1 p sep@ applies /one/ or more occurrences of @p@, separated -- by @sep@. Returns a list of the values returned by @p@. -- -- > commaSep p = p `sepBy` (symbol ",") sepBy1 :: Alternative f => f a -> f s -> f [a] sepBy1 p s = scan where scan = liftA2 (:) p ((s *> scan) <|> pure []) -- | @manyTill p end@ applies action @p@ /zero/ or more times until -- action @end@ succeeds, and returns the list of values returned by -- @p@. This can be used to scan comments: -- -- > simpleComment = string "")) -- -- Note the overlapping parsers @anyChar@ and @string \"