fastparser-0.3.1.2: A fast, but bare bones, bytestring parser combinators library.

Safe HaskellNone
LanguageHaskell2010

ByteString.Parser.Fast

Contents

Description

A fast parser combinators module.

This module is extremely bare-bones, and provides only very limited functionality.

Sample usage:

module Syslog where

import ByteString.Parser.Fast
import qualified Data.ByteString as BS
import Data.Thyme.Clock
import Control.Applicative

data SyslogMsg
    = SyslogMsg
    { _syslogPrio    :: {-# UNPACK #-} !Int
    , _syslogTS      :: {-# UNPACK #-} !UTCTime
    , _syslogHost    :: !BS.ByteString
    , _syslogProgram :: !BS.ByteString
    , _syslogPID     :: !(Maybe Int)
    , _syslogData    :: !BS.ByteString
    } deriving (Show, Eq)


syslogMsg :: Parser SyslogMsg
syslogMsg = do
    char '<'
    prio <- decimal
    char '>'
    ts <- rfc3339
    char ' '
    host <- charTakeWhile1 (/= ' ')
    char ' '
    program <- charTakeWhile1 (\x -> x /= ':' && x /= '[')
    pid' <- optional (char '[' *> decimal <* char ']')
    char ':'
    dt <- remaining
    return (SyslogMsg prio ts host program pid' dt)

test :: BS.ByteString -> Either ParseError SyslogMsg
test = parseOnly syslogMsg
Synopsis

Documentation

newtype ParserM a Source #

A parser, church encoded. The arguments to the wrapped function are:

  • Input ByteString.
  • A function that handles parse errors.
  • A function that handles success, taking as argument the remaining input and the parser result.

Constructors

Parser 

Fields

Instances
Monad ParserM Source # 
Instance details

Defined in ByteString.Parser.Fast

Methods

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

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

return :: a -> ParserM a #

fail :: String -> ParserM a #

Functor ParserM Source # 
Instance details

Defined in ByteString.Parser.Fast

Methods

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

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

Applicative ParserM Source # 
Instance details

Defined in ByteString.Parser.Fast

Methods

pure :: a -> ParserM a #

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

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

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

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

Alternative ParserM Source # 
Instance details

Defined in ByteString.Parser.Fast

Methods

empty :: ParserM a #

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

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

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

MonadPlus ParserM Source # 
Instance details

Defined in ByteString.Parser.Fast

Methods

mzero :: ParserM a #

mplus :: ParserM a -> ParserM a -> ParserM a #

parseOnly :: Parser a -> ByteString -> Either ParseError a Source #

Runs the parser. Will return a parse error if the parser fails or if the input is not completely consumed.

Error handling

ueof :: ParseError Source #

An error representing the unexpected end of input.

ufail Source #

Arguments

:: String

The expected label.

-> ParseError 

A generic error.

parseError Source #

Arguments

:: ByteString

Unexpected content

-> ByteString

Expected content

-> ParseError 

Creates a generic parse error.

Parsing numerical values

decimal :: Parser Int Source #

parses a decimal integer.

num :: Num n => Parser n Source #

Parses any positive decimal Num.

hnum :: Num n => Parser n Source #

Parses any positive hexadecimal Num.

onum :: Num n => Parser n Source #

Parses any positives octal Num.

frac :: Fractional a => Parser a Source #

Parses Fractional numbers.

scientific :: Parser Double Source #

A fast parser for numbers of the form 5.123. Contrary to what its name implies, it parses to Double.

Parsing characters

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

Parses a character satisfying a predicate

anyChar :: Parser Char Source #

Parses any character.

char :: Char -> Parser () Source #

Parses a specific character.

string :: ByteString -> Parser () Source #

Parses the supplied string.

quotedString :: Parser ByteString Source #

Parses strings between double quotes. This functions handles the following escape sequences: \r, \n, \t, \a, \b, \", \\.

Various combinators

takeN :: Int -> Parser ByteString Source #

Consumes n bytes of input

remaining :: Parser ByteString Source #

Parses the remaining input.

charTakeWhile :: (Char -> Bool) -> Parser ByteString Source #

Consumes the input as long as the predicate remains true.

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

Consumes the input as long as the predicate remains true.

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

Discards the input as long as the predicate remains true.

Parsing time-related values

parseYMD :: Parser Day Source #

Parses days, with format YYYY-MM-DD

parseDTime :: Parser DiffTime Source #

Parses a difftime, with format HH:MM:SS

timestamp :: Parser UTCTime Source #

Parses a whole timestamp, with format YYYY-MM-DD+HH:MM:SS+CEST. This is very much *not* robust, as it only handles CET and CEST.

rfc3339 :: Parser UTCTime Source #

Parses RFC3339 compatible timestamps to UTCTime.

Interfacing with other libraries

wlex :: (ByteString -> Maybe (a, ByteString)) -> Parser a Source #

Creates a parser from the supplied function. The first argument to the supplied function is the remaining input, and it should return Nothing when parsing failes, or Just the result along with the non-consumed input.

It works well with the bytestring-lexing library.

pFold :: Parser a -> SimpleFold ByteString a Source #

Turns any parser into a SimpleFold.

Hacks and bits

isLower :: Word8 -> Bool Source #

Returns true when the character represents an ASCII lowercase letter.

getOctal :: ByteString -> Int Source #

Parses bytestrings as if they were representing an octal number in ASCII.

getInt :: ByteString -> Int Source #

Parses bytestrings as if they were representing a decimal number in ASCII.