phaser-1.0.0.0: Incremental multiple pass parser library.

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

Codec.Phaser.Core

Description

Core functions and types.

Synopsis

Documentation

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 # 

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 # 

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 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 # 

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 # 

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 # 

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 # 

Methods

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

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

(*>) :: 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 # 

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 # 

Methods

mzero :: Phase p i o a #

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

get :: Phase p i o i Source #

Return one item of the input.

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

Put a list of values back into the input.

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

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

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

Modify the counter

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

Yield one item for the incremental output

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

Fail if any more input is provided.

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

Fail unless more input is provided.

(<?>) :: [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

(>>#) :: (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.

(>#>) :: (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.

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

Remove an Automaton's ability to consume further input

class PhaserType s where Source #

Class for types which consume and produce incremental input and output.

Minimal complete definition

toAutomaton, fromAutomaton, toPhase, fromPhase, ($#$)

Methods

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

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

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

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

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

Instances

PhaserType Phase Source # 

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 #

PhaserType Automaton Source # 

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 #

fitYield :: PhaserType s => s p i Void a -> s p i o a Source #

Take a Phase or Automaton which doesn't yield anything and allow it to be used in a chain containing yield statements

beforeStep :: Monoid p => Automaton p i o a -> Either (Automaton p v o a) (Automaton p i o a) Source #

Optional pre-processing of an automaton before passing it more input. Produces Right with all "final outputs" and errors stripped if the automaton can accept more input, and Left with everything except errors stripped if it cannot accept more input.

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.

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

Create a ReadS like value from a Phaser type. If the input type is Char, the result will be ReadS

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

Pass a list of input values to an Automaton

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.

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

Use a Phase as a parser, but consuming a single input instead of a list

options :: Automaton p i o a -> [Automaton p i o a] Source #

Decompose an Automaton into its component options.

readCount :: Monoid p => Automaton p i o a -> (p, Automaton p i o a) Source #

Separate unconditional counter modifiers from an automaton

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

Separate the values unconditionally yielded by an automaton

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

Run a Phaser object on input values produced by a monadic action and passing the output values to another monadic function. The input action should return Nothing when there is no more input. If there is more than one final result: the left one is chosen, and all the outputs leading to it are also output.