phaser-1.0.1.0: Incremental multiple pass parser library.

CopyrightJeremy List
LicenseBSD-3
Maintainerquick.dudley@gmail.com
Safe HaskellNone
LanguageHaskell2010

Codec.Phaser

Description

 
Synopsis

Documentation

data Phase p i o a Source #

A type for building Automaton values. Monad and Applicative instances are defined for this type rather than for Automaton in order to avoid traversing the entire call stack for every input value.

Instances
PhaserType Phase Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

toAutomaton :: Monoid p => Phase p i o a -> Automaton p i o a Source #

fromAutomaton :: Monoid p => Automaton p i o a -> Phase p i o a Source #

toPhase :: Monoid p => Phase p i o a -> Phase p i o a Source #

fromPhase :: Monoid p => Phase p i o a -> Phase p i o a Source #

($#$) :: Monoid p => Phase p b c x -> (c -> t) -> Phase p b t x Source #

Monad (Phase p i o) Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

(>>=) :: Phase p i o a -> (a -> Phase p i o b) -> Phase p i o b #

(>>) :: Phase p i o a -> Phase p i o b -> Phase p i o b #

return :: a -> Phase p i o a #

fail :: String -> Phase p i o a #

Functor (Phase p i o) Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

fmap :: (a -> b) -> Phase p i o a -> Phase p i o b #

(<$) :: a -> Phase p i o b -> Phase p i o a #

Applicative (Phase p i o) Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

pure :: a -> Phase p i o a #

(<*>) :: Phase p i o (a -> b) -> Phase p i o a -> Phase p i o b #

liftA2 :: (a -> b -> c) -> Phase p i o a -> Phase p i o b -> Phase p i o c #

(*>) :: Phase p i o a -> Phase p i o b -> Phase p i o b #

(<*) :: Phase p i o a -> Phase p i o b -> Phase p i o a #

Monoid p => Alternative (Phase p i o) Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

empty :: Phase p i o a #

(<|>) :: Phase p i o a -> Phase p i o a -> Phase p i o a #

some :: Phase p i o a -> Phase p i o [a] #

many :: Phase p i o a -> Phase p i o [a] #

Monoid p => MonadPlus (Phase p i o) Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

mzero :: Phase p i o a #

mplus :: Phase p i o a -> Phase p i o a -> Phase p i o a #

data Automaton p i o a Source #

Represents a nondeterministic computation in progress. There are 4 type parameters: a counter type (may be used for tracking line and column numbers), an input type, an incremental output type, and a final output type.

Instances
PhaserType Automaton Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

toAutomaton :: Monoid p => Automaton p i o a -> Automaton p i o a Source #

fromAutomaton :: Monoid p => Automaton p i o a -> Automaton p i o a Source #

toPhase :: Monoid p => Automaton p i o a -> Phase p i o a Source #

fromPhase :: Monoid p => Phase p i o a -> Automaton p i o a Source #

($#$) :: Monoid p => Automaton p b c x -> (c -> t) -> Automaton p b t x Source #

Functor (Automaton p i o) Source # 
Instance details

Defined in Codec.Phaser.Core

Methods

fmap :: (a -> b) -> Automaton p i o a -> Automaton p i o b #

(<$) :: a -> Automaton p i o b -> Automaton p i o a #

data Position Source #

A data type for describing a position in a text file. Constructor arguments are row number and column number.

Constructors

Position !Int !Int 

class Standardized r a where Source #

Class for types which have standardized or otherwise unambiguous representations. Implementations of regular may be more permissive than the corresponding Read instance (if any).

Methods

regular :: Monoid p => Phase p r o a Source #

Instances
Standardized Char Bool Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Bool Source #

Standardized Char Double Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Double Source #

Standardized Char Float Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Float Source #

Standardized Char Int Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Int Source #

Standardized Char Int8 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Int8 Source #

Standardized Char Int16 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Int16 Source #

Standardized Char Int32 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Int32 Source #

Standardized Char Int64 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Int64 Source #

Standardized Char Integer Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Integer Source #

Standardized Char Word Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Word Source #

Standardized Char Word8 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Word8 Source #

Standardized Char Word16 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Word16 Source #

Standardized Char Word32 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Word32 Source #

Standardized Char Word64 Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o Word64 Source #

(Integral a, Standardized Char a) => Standardized Char (Ratio a) Source # 
Instance details

Defined in Codec.Phaser.Common

Methods

regular :: Monoid p => Phase p Char o (Ratio a) Source #

(>>#) :: (Monoid p, PhaserType s, PhaserType d) => s p b c x -> d p c t a -> Automaton p b t a infixr 4 Source #

Take the incremental output of the first argument and use it as input for the second argument. Discard the final output of the first argument.

(>#>) :: forall s p0 p i o a. (PhaserType s, Monoid p0, Monoid p) => (p0 -> p) -> s p0 i o a -> s p i o a infixr 1 Source #

Change the counter type of a Phaser object. May cause getCount to behave differently from expected: counter increments inside the right hand argument are visible outside but not vice versa.

(<?>) :: [Char] -> Phase p i o a -> Phase p i o a infixr 1 Source #

If parsing fails in the right argument: prepend the left argument to the errors

($#$) :: (PhaserType s, Monoid p) => s p b c x -> (c -> t) -> s p b t x infixl 5 Source #

parse :: PhaserType s => s Position i o a -> [i] -> Either [(Position, [String])] [a] Source #

Use a Phase as a parser. Note that unlike other parsers the reported position in the input when the parser fails is the position reached when all parsing options are exhausted, not the beginning of the failing token. Since the characters may be counted nondeterministically: if multiple errors are returned the reported error position may be different for each error report.

parse_ :: (Monoid p, PhaserType s) => p -> s p i o a -> [i] -> Either [(p, [String])] [a] Source #

Use a Phase value similarly to a parser.

parseFile :: PhaserType s => s Position Word8 o a -> FilePath -> IO (Either [(Position, [String])] [a]) Source #

Run a parser on input from a file. Input is provided as bytes, if characters are needed: a decoding phase such as utf8_stream or latin1 may be used.

parseFile_ :: (Monoid p, PhaserType s) => p -> s p Word8 o a -> FilePath -> IO (Either [(p, [String])] [a]) Source #

Run a parser on input from a file. Input is provided as bytes, if characters are needed: a decoding phase such as utf8_stream or latin1 may be used. Counter type agnostic version.

parseHandle :: PhaserType s => s Position Word8 o a -> Handle -> IO (Either [(Position, [String])] [a]) Source #

Run a parser on input from a handle. Input is provided as bytes, if characters are needed: a decoding phase such as utf8_stream may be used.

parseHandle_ :: (Monoid p, PhaserType s) => p -> s p Word8 o a -> Handle -> IO (Either [(p, [String])] [a]) Source #

Run a parser from the contents of a Handle. Input is provided as bytes.

get :: Phase p i o i Source #

Return one item of the input.

count :: p -> Phase p i o () Source #

Increment the counter

yield :: o -> Phase p i o () Source #

Yield one item for the incremental output

put1 :: Monoid p => i -> Phase p i o () Source #

Insert one value back into the input. May be used for implementing lookahead

put :: Monoid p => [i] -> Phase p i o () Source #

Put a list of values back into the input.

run :: Monoid p => Automaton p i o a -> [i] -> Automaton p i o a Source #

Pass a list of input values to an Automaton

step :: Monoid p => Automaton p i o a -> i -> Automaton p i o a Source #

Pass one input to an automaton

extract :: Monoid p => p -> Automaton p i o a -> Either [(p, [String])] [a] Source #

Take either counters with errors or a list of possible results from an automaton.

satisfy :: Monoid p => (i -> Bool) -> Phase p i o i Source #

Consume one input, return it if it matches the predicate, otherwise fail.

match :: (Eq i, Monoid p) => i -> Phase p i o i Source #

Consume one input, if it's equal to the parameter then return it, otherwise fail.

char :: Monoid p => Char -> Phase p Char o Char Source #

match specialized to Char

iChar :: Monoid p => Char -> Phase p Char o Char Source #

Case insensitive version of char

string :: (Eq i, Monoid p) => [i] -> Phase p i o [i] Source #

Match a list of input values

iString :: Monoid p => String -> Phase p Char o String Source #

Match a string (case insensitive)

integer :: (Num a, Monoid p) => Phase p Char o a Source #

Parse a number either from decimal digits or from hexadecimal prefixed with "0x"

decimal :: (Fractional a, Monoid p) => Phase p Char o a Source #

Parse a number from decimal digits, "-", and "."

scientificNotation :: (Fractional a, Monoid p) => Phase p Char o a Source #

Parse a number from standard decimal format or from scientific notation.

sepBy :: Monoid p => Phase p i o a -> Phase p i o s -> Phase p i o [a] Source #

sepBy p sep parses zero or more occurrences of p, separated by sep. Returns a list of values returned by p.

munch :: Monoid p => (i -> Bool) -> Phase p i o [i] Source #

Parses the first zero or more values satisfying the predicate. Always succeds, exactly once, having consumed all the characters Hence NOT the same as (many (satisfy p))

munch1 :: Monoid p => (i -> Bool) -> Phase p i o [i] Source #

Parses the first one or more values satisfying the predicate. Succeeds if at least one value matches, having consumed all the characters Hence NOT the same as (some (satisfy p))

trackPosition :: Phase Position Char Char () Source #

Count the lines and characters from the input before yielding them again. If the phase pipeline does not include this or similar: parsing errors will not report the correct position. Unix, Windows, Mac-OS Classic, and Acorn newline formats are all recognized.