phaser-0.1.1.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

Link Phase Automaton Phase Source # 

Methods

(>>#) :: Phase p b c x -> Automaton p c t a -> Phase p b t a Source #

Link Automaton Automaton Automaton Source # 

Methods

(>>#) :: Automaton p b c x -> Automaton p c t a -> Automaton p b t a 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

Link Phase Phase Phase Source # 

Methods

(>>#) :: Phase p b c x -> Phase p c t a -> Phase p b t a Source #

Link Phase Automaton Phase Source # 

Methods

(>>#) :: Phase p b c x -> Automaton p c t a -> Phase p b t a 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 #

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

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 #

class Link s d l | s d -> l where Source #

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

Minimal complete definition

(>>#)

Methods

(>>#) :: s p b c x -> d p c t a -> l 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.

get :: Phase p i o i Source #

Return one item of the input.

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

Put a list of values back into the input.

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

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

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

Modify the counter

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

Yield one item for the incremental output

eof :: Phase p i o () Source #

Fail if any more input is provided.

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

Warning: ?? is faulty and will be removed in future versions. Please use ? instead

When the right argument fails: apply the left argument to the list of error messages. Depreciated because it doesn't work correctly for all arguments and fixing it would break the Alternative and MonadPlus instances.

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

(>#>) :: ((p0 -> p0) -> p -> p) -> Phase p0 i o a -> Phase p i o a infixr 1 Source #

Change the counter type of a Phase object.

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

Remove an Automaton's ability to consume further input

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

Convert a Phase to an Automaton. Subject to fusion.

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

Convert an Automaton back to a Phase (somewhat inefficient). Subject to fusion.

beforeStep :: 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 :: Automaton p i o a -> i -> Automaton p i o a Source #

Pass one input to an automaton

extract :: 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 :: Automaton p i o a -> [i] -> [(a, [i])] Source #

Create a ReadS like value from an Automaton. If the Automaton's input type is Char, the result will be ReadS

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

Pass a list of input values to an Automaton

parse_ :: p -> Phase p i o a -> [i] -> Either [(p, [String])] [a] Source #

Use a Phase value similarly to a parser.

parse1_ :: p -> Phase 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 :: Automaton p i o a -> (p -> p, Automaton p i o a) Source #

Separate unconditional counter modifiers from an automaton

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

Separate the values unconditionally yielded by an automaton