snack-0.1.0.0: Strict ByteString Parser Combinator
LicenseCC0-1.0
Maintainermordae@anilinux.org
Stabilityunstable
Portabilitynon-portable (ghc)
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.ByteString.Parser

Description

This module provides a parser for ByteString.

  • If you'd like to parse ASCII text, you might want to take a look at Data.ByteString.Parser.Char8. It reuses the same Parser, but provides functions working with Char instead of Word8 as well as more string utilities.
  • If you'd like to parse Unicode text, look instead at the Data.Text.Parser. Is is slower, but in a way more correct.
Synopsis

Documentation

newtype Parser a Source #

Constructors

Parser 

Fields

Instances

Instances details
MonadFail Parser Source # 
Instance details

Defined in Data.ByteString.Parser

Methods

fail :: String -> Parser a #

Alternative Parser Source # 
Instance details

Defined in Data.ByteString.Parser

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

Applicative Parser Source # 
Instance details

Defined in Data.ByteString.Parser

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

liftA2 :: (a -> b -> c) -> Parser a -> Parser b -> Parser c #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Functor Parser Source # 
Instance details

Defined in Data.ByteString.Parser

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Monad Parser Source # 
Instance details

Defined in Data.ByteString.Parser

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

MonadPlus Parser Source # 
Instance details

Defined in Data.ByteString.Parser

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

parseOnly :: Parser a -> ByteString -> Maybe a Source #

Discards the remaining input and returns just the parse result. You might want to combine it with endOfInput for the best effect.

Example:

parseOnly (pContacts <* endOfInput) bstr

Bytes

byte :: Word8 -> Parser Word8 Source #

Accepts a single, matching byte.

notByte :: Word8 -> Parser Word8 Source #

Accepts a single, differing byte.

anyByte :: Parser Word8 Source #

Accepts a single byte.

satisfy :: (Word8 -> Bool) -> Parser Word8 Source #

Accepts a single byte matching the predicate.

peekByte :: Parser Word8 Source #

Peeks ahead, but does not consume.

Be careful, peeking behind end of the input fails. You might want to check using atEnd beforehand.

Strings

string :: ByteString -> Parser ByteString Source #

Accepts a matching string.

take :: Int -> Parser ByteString Source #

Accepts given number of bytes. Fails when not enough bytes are available.

scan :: s -> (s -> Word8 -> Maybe s) -> Parser ByteString Source #

Scans ahead statefully and then accepts whatever bytes the scanner liked. Scanner returns Nothing to mark end of the acceptable extent.

runScanner :: s -> (s -> Word8 -> Maybe s) -> Parser (ByteString, s) Source #

Like scan, but also returns the final scanner state.

takeWhile :: (Word8 -> Bool) -> Parser ByteString Source #

Efficiently consume as long as the input bytes match the predicate. An inverse of takeTill.

takeWhile1 :: (Word8 -> Bool) -> Parser ByteString Source #

Like takeWhile, but requires at least a single byte.

takeTill :: (Word8 -> Bool) -> Parser ByteString Source #

Efficiently consume until a byte matching the predicate is found. An inverse of takeWhile.

takeTill1 :: (Word8 -> Bool) -> Parser ByteString Source #

Same as takeTill, but requires at least a single byte.

Combinators

provided :: (Alternative m, Monad m) => (a -> Bool) -> m a -> m a Source #

Fails if the value returned by the parser does not conform to the predicate. Generalized form of string.

Example:

pInput = takeWhile isLetter provided (odd . length)

choice :: Alternative f => [f a] -> f a Source #

Tries various parsers, one by one. Alias for asum.

Example:

pExpression = choice [ pConstant
                     , pVariable
                     , pBinaryOperation
                     , pFunctionApplication
                     ]

count :: Monad m => Int -> m a -> m [a] Source #

Replicates the parser given number of times, collecting the results in a list. Fails if any instance of the parser fails.

Example:

pFourWords = (:) <$> word <*> count 3 (blank *> word)
  where word  = takeWhile1 isLetter
        blank = takeWhile1 isSpace

optional :: Alternative f => f a -> f (Maybe a) #

One or none.

It is useful for modelling any computation that is allowed to fail.

Examples

Expand

Using the Alternative instance of Control.Monad.Except, the following functions:

>>> import Control.Monad.Except
>>> canFail = throwError "it failed" :: Except String Int
>>> final = return 42                :: Except String Int

Can be combined by allowing the first function to fail:

>>> runExcept $ canFail *> final
Left "it failed"
>>> runExcept $ optional canFail *> final
Right 42

eitherP :: Alternative f => f a -> f b -> f (Either a b) Source #

Captures first parser as Left or the second as Right.

option :: Alternative f => a -> f a -> f a Source #

Shortcut for optional with a default value.

Example:

data Contact =
 Contact
   { contactName  :: Text
   , contactEmail :: Maybe Text
   }

pContact = Contact <$> pFullName <*> option pEmail

many :: Alternative f => f a -> f [a] #

Zero or more.

many1 :: Alternative f => f a -> f [a] Source #

Like many1, but requires at least one match.

manyTill :: Alternative f => f a -> f a -> f [a] Source #

Like many, but stops once the second parser matches the input ahead.

Example:

pBodyLines = pLine manyTill pEnd
  where pLine = takeTill (== 'n')
        pEnd  = string "n.n"

sepBy :: Alternative f => f a -> f b -> f [a] Source #

Similar to many, but interleaves the first parser with the second.

Example:

pLines = pLine sepBy char 'n'

sepBy1 :: Alternative f => f a -> f b -> f [a] Source #

Like sepBy, but requires at least one match.

wrap :: Applicative f => f a -> f b -> f a Source #

Wraps the parser from both sides.

Example:

pToken = takeWhile1 (inClass "A-Za-z0-9_") wrap takeWhile isSpace

match :: Parser a -> Parser (ByteString, a) Source #

Makes the parser not only return the result, but also the original matched extent.

End Of Input

takeByteString :: Parser ByteString Source #

Accept whatever input remains.

endOfInput :: Parser () Source #

Accepts end of input and fails if we are not there yet.

atEnd :: Parser Bool Source #

Returns whether we are at the end of the input yet.

Miscelaneous

These are all generic methods, but since I sometimes forget about them, it is nice to have them listed here for reference what writing parsers.

empty :: Alternative f => f a #

The identity of <|>

pure :: Applicative f => a -> f a #

Lift a value.

guard :: Alternative f => Bool -> f () #

Conditional failure of Alternative computations. Defined by

guard True  = pure ()
guard False = empty

Examples

Expand

Common uses of guard include conditionally signaling an error in an error monad and conditionally rejecting the current choice in an Alternative-based parser.

As an example of signaling an error in the error monad Maybe, consider a safe division function safeDiv x y that returns Nothing when the denominator y is zero and Just (x `div` y) otherwise. For example:

>>> safeDiv 4 0
Nothing
>>> safeDiv 4 2
Just 2

A definition of safeDiv using guards, but not guard:

safeDiv :: Int -> Int -> Maybe Int
safeDiv x y | y /= 0    = Just (x `div` y)
            | otherwise = Nothing

A definition of safeDiv using guard and Monad do-notation:

safeDiv :: Int -> Int -> Maybe Int
safeDiv x y = do
  guard (y /= 0)
  return (x `div` y)

when :: Applicative f => Bool -> f () -> f () #

Conditional execution of Applicative expressions. For example,

when debug (putStrLn "Debugging")

will output the string Debugging if the Boolean value debug is True, and otherwise do nothing.

unless :: Applicative f => Bool -> f () -> f () #

The reverse of when.

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int ():

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2