Skip to content

Commit

Permalink
Miscellaneous changes
Browse files Browse the repository at this point in the history
Rename eof to endOfInput
Make sure that the Combinator module is re-exported
  • Loading branch information
bos committed Jan 14, 2009
1 parent 558bb62 commit bec9844
Show file tree
Hide file tree
Showing 6 changed files with 69 additions and 16 deletions.
5 changes: 4 additions & 1 deletion Data/Attoparsec.hs
Expand Up @@ -28,7 +28,7 @@ module Data.Attoparsec

-- * Things vaguely like those in @Parsec.Combinator@ (and @Parsec.Prim@)
, try
, eof
, endOfInput
, lookAhead
, peek

Expand All @@ -53,7 +53,10 @@ module Data.Attoparsec
, skipWhile
, notEmpty
, match

, module Data.Attoparsec.Combinator
) where

import Data.Attoparsec.Combinator
import Data.Attoparsec.Internal
import Prelude hiding (takeWhile)
8 changes: 5 additions & 3 deletions Data/Attoparsec/Char8.hs
Expand Up @@ -29,7 +29,7 @@ module Data.Attoparsec.Char8

-- * Things vaguely like those in @Parsec.Combinator@ (and @Parsec.Prim@)
, try
, eof
, endOfInput
, lookAhead
, peek

Expand Down Expand Up @@ -67,18 +67,20 @@ module Data.Attoparsec.Char8
, inClass
, notInClass
, endOfLine

, module Data.Attoparsec.Combinator
) where

import Control.Applicative ((<$>))
import qualified Data.ByteString.Char8 as SB
import qualified Data.ByteString.Lazy.Char8 as LB
import Data.ByteString.Internal (w2c)
import Data.Char (isDigit, isLetter, isSpace, toLower)
import Data.Attoparsec.FastSet
(FastSet, memberChar, set)
import qualified Data.Attoparsec.Internal as I
import Data.Attoparsec.Combinator
import Data.Attoparsec.Internal
(Parser, ParseError, (<?>), parse, parseAt, parseTest, try, eof,
(Parser, ParseError, (<?>), parse, parseAt, parseTest, try, endOfInput,
lookAhead, peek, string,
eitherP, getInput, getConsumed, takeAll, takeCount, notEmpty, match,
endOfLine, setInput)
Expand Down
41 changes: 37 additions & 4 deletions Data/Attoparsec/Combinator.hs
Expand Up @@ -2,12 +2,12 @@
-----------------------------------------------------------------------------
-- |
-- Module : Data.Attoparsec.Combinator
-- Copyright : Bryan O'Sullivan 2009
-- Copyright : Daan Leijen 1999-2001, Bryan O'Sullivan 2009
-- License : BSD3
--
-- Maintainer : bos@serpentine.com
-- Stability : experimental
-- Portability : unknown
-- Portability : portable
--
-- Useful parser combinators, similar to Parsec.
--
Expand All @@ -16,29 +16,62 @@ module Data.Attoparsec.Combinator
(
choice
, count
, many
, option
, many1
, manyTill
, sepBy
, sepBy1
, skipMany
, skipMany1
, module Control.Applicative
) where

import Control.Applicative

-- | @choice ps@ tries to apply the parsers in the list @ps@ in order,
-- until one of them succeeds. Returns the value of the succeeding
-- parser.
choice :: Alternative f => [f a] -> f a
choice = foldr (<|>) empty

-- | @option x p@ tries to apply parser @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 parser @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)

-- | @sepBy p sep@ parses /zero/ or more occurrences of @p@, separated
-- by @sep@. Returns a list of 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@ parses /one/ or more occurrences of @p@, separated
-- by @sep@. Returns a list of values returned by @p@.
--
-- > commaSep p = p `sepBy` (symbol ",")
sepBy1 :: Alternative f => f a -> f s -> f [a]
sepBy1 p s = liftA2 (:) p ((s *> sepBy1 p s) <|> pure [])
sepBy1 p s = scan
where scan = liftA2 (:) p ((s *> scan) <|> pure [])

-- | @manyTill p end@ applies parser @p@ /zero/ or more times until
-- parser @end@ succeeds. Returns the list of values returned by @p@.
-- This parser can be used to scan comments:
--
-- > simpleComment = string "<!--" *> manyTill anyChar (try (string "-->"))
--
-- Note the overlapping parsers @anyChar@ and @string \"<!--\"@, and
-- therefore the use of the 'try' combinator.
manyTill :: Alternative f => f a -> f b -> f [a]
manyTill p end = scan
where scan = (end *> pure []) <|> liftA2 (:) p scan
Expand Down
15 changes: 14 additions & 1 deletion Data/Attoparsec/Incremental.hs
Expand Up @@ -25,11 +25,13 @@ module Data.Attoparsec.Incremental
, parseTest

, (<?>)
, try
, takeWhile
, takeTill
, takeCount
, string
, satisfy
, endOfInput
, pushBack

, word8
Expand All @@ -39,9 +41,11 @@ module Data.Attoparsec.Incremental
, skipWhile

, yield

, module Data.Attoparsec.Combinator
) where

import Control.Applicative
import Data.Attoparsec.Combinator
import Control.Monad (MonadPlus(..), ap)
import Data.Attoparsec.Internal ((+:))
import Data.Word (Word8)
Expand Down Expand Up @@ -133,6 +137,9 @@ plus p1 p2 =
in
filt $ unParser p1 (S sb lb [] eof (failDepth + 1)) (cutContinuation k)

try :: Parser r a -> Parser r a
try p = p

instance Functor (Parser r) where
fmap f m = Parser $ \s cont -> unParser m s (cont . f)

Expand Down Expand Up @@ -234,6 +241,12 @@ pushBack bs =
Parser $ \(S sb lb adds eof failDepth) k ->
k () (mkState (bs `appL` (sb +: lb)) adds eof failDepth)

endOfInput :: Parser r ()
endOfInput = Parser $ \st@(S sb lb _adds _eof _failDepth) k ->
if not (S.null sb) || not (L.null lb)
then IFailed st "endOfInput: not EOF"
else continue (k ()) endOfInput k st

toplevelTranslate :: IResult a -> Result a
toplevelTranslate (IFailed _ err) = Failed err
toplevelTranslate (IDone (S sb lb _ _ _) value) = Done (sb +: lb) value
Expand Down
6 changes: 4 additions & 2 deletions Data/Attoparsec/Incremental/Char8.hs
Expand Up @@ -2,7 +2,7 @@
-----------------------------------------------------------------------------
-- |
-- Module : Data.Attoparsec.Incremental.Char8
-- Copyright : Daan Leijen 1999-2001, Jeremy Shaw 2006, Bryan O'Sullivan 2007-2008
-- Copyright : Bryan O'Sullivan 2009
-- License : BSD3
--
-- Maintainer : bos@serpentine.com
Expand Down Expand Up @@ -51,9 +51,10 @@ module Data.Attoparsec.Incremental.Char8
, skipSpace
, inClass
, notInClass

, module Data.Attoparsec.Combinator
) where

import Control.Applicative ((<$>))
import qualified Data.ByteString.Char8 as SB
import qualified Data.ByteString.Lazy.Char8 as LB
import Data.ByteString.Internal (w2c)
Expand All @@ -66,6 +67,7 @@ import Data.Attoparsec.Incremental
string, takeCount)
import Data.ByteString.Lex.Lazy.Double (readDouble)
import Prelude hiding (takeWhile)
import Data.Attoparsec.Combinator

numeric :: String -> (Char -> Bool)
-> (LB.ByteString -> Maybe (a,LB.ByteString)) -> Parser r a
Expand Down
10 changes: 5 additions & 5 deletions Data/Attoparsec/Internal.hs
Expand Up @@ -29,7 +29,7 @@ module Data.Attoparsec.Internal

-- * Things vaguely like those in @Parsec.Combinator@ (and @Parsec.Prim@)
, try
, eof
, endOfInput
, lookAhead
, peek

Expand Down Expand Up @@ -221,10 +221,10 @@ try p = Parser $ \s@(S sb lb _) ->
ok -> ok

-- | Detect 'end of file'.
eof :: Parser ()
eof = Parser $ \s@(S sb lb _) -> if SB.null sb && LB.null lb
then Right ((), s)
else Left (sb +: lb, ["EOF"])
endOfInput :: Parser ()
endOfInput = Parser $ \s@(S sb lb _) -> if SB.null sb && LB.null lb
then Right ((), s)
else Left (sb +: lb, ["EOF"])

takeAll :: Parser LB.ByteString
takeAll = Parser $ \(S sb lb n) ->
Expand Down

0 comments on commit bec9844

Please sign in to comment.