Copyright | Jeremy List |
---|---|
License | BSD-3 |
Maintainer | quick.dudley@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Core functions and types.
Synopsis
- data Automaton p i o a
- data Phase p i o a
- get :: Phase p i o i
- put :: Monoid p => [i] -> Phase p i o ()
- put1 :: Monoid p => i -> Phase p i o ()
- buffer :: (Monoid p, PhaserType s) => s () i i Bool -> Phase p i o ()
- count :: p -> Phase p i o ()
- getCount :: Phase p i o p
- yield :: o -> Phase p i o ()
- eof :: Monoid p => Phase p i o ()
- neof :: Monoid p => Phase p i o ()
- (<?>) :: [Char] -> Phase p i o a -> Phase p i o a
- chainWith :: forall p s d x a z b t c. (Monoid p, PhaserType s, PhaserType d) => (x -> a -> z) -> s p b c x -> d p c t a -> Automaton p b t z
- (>>#) :: (Monoid p, PhaserType s, PhaserType d) => s p b c x -> d p c t a -> Automaton p b t a
- (>#>) :: 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
- starve :: Monoid p => Automaton p i o a -> Automaton p z o a
- class PhaserType s where
- fitYield :: PhaserType s => s p i Void a -> s p i o a
- fitGet :: PhaserType s => s p Void o a -> s p i o a
- beforeStep :: Monoid p => Automaton p i o a -> Either (Automaton p v o a) (Automaton p i o a)
- step :: Monoid p => Automaton p i o a -> i -> Automaton p i o a
- extract :: Monoid p => p -> Automaton p i o a -> Either [(p, [String])] [a]
- toReadS :: (PhaserType s, Monoid p) => s p i o a -> [i] -> [(a, [i])]
- run :: Monoid p => Automaton p i o a -> [i] -> Automaton p i o a
- parse_ :: (Monoid p, PhaserType s) => p -> s p i o a -> [i] -> Either [(p, [String])] [a]
- parse1_ :: (Monoid p, PhaserType s) => p -> s p i o a -> i -> Either [(p, [String])] [a]
- options :: Monoid p => Automaton p i o a -> [Automaton p i o a]
- readCount :: Monoid p => Automaton p i o a -> (p, Automaton p i o a)
- outputs :: Monoid p => Automaton p i o a -> ([o], Automaton p i o a)
- stream :: (Monoid p, PhaserType s, Monad m) => p -> s p i o a -> m (Maybe [i]) -> ([o] -> m ()) -> m (Either [(p, [String])] a)
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 # | |
Defined in Codec.Phaser.Core 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 # | |
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 # | |
Defined in Codec.Phaser.Core 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 # | |
MonadFail (Phase p i o) Source # | |
Defined in Codec.Phaser.Core | |
Monoid p => Alternative (Phase p i o) Source # | |
Applicative (Phase p i o) Source # | |
Defined in Codec.Phaser.Core | |
Functor (Phase p i o) Source # | |
Monad (Phase p i o) Source # | |
Monoid p => MonadPlus (Phase p i o) Source # | |
put :: Monoid p => [i] -> Phase p i o () Source #
Put a list of values back into the input. Can have counter-intuitive
interactions with getCount
put1 :: Monoid p => i -> Phase p i o () Source #
Insert one value back into the input. May be used for implementing
lookahead. Can have counter-intuitive interactions with getCount
.
buffer :: (Monoid p, PhaserType s) => s () i i Bool -> Phase p i o () Source #
Use the argument to control the input passed to the following Phase
actions.
buffer (return True)
is equivalent to
return ()
buffer (return False)
is equivalent to
eof
buffer (True <$ yield
is equivalent to
@
put1 a
)
a
*
etc.
getCount :: Phase p i o p Source #
Retrieve the current counter. Counter values are shared between arguments
to >>#
except when at least one argument is produced by an incompatible function.
All functions in this module are compatible unless noted in the corresponding
documentation.
(<?>) :: [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
chainWith :: forall p s d x a z b t c. (Monoid p, PhaserType s, PhaserType d) => (x -> a -> z) -> s p b c x -> d p c t a -> Automaton p b t z 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.
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.
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 Automaton Source # | |
Defined in Codec.Phaser.Core 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 # | |
PhaserType Phase Source # | |
Defined in Codec.Phaser.Core 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 # |
fitYield :: PhaserType s => s p i Void a -> s p i o a Source #
fitGet :: PhaserType s => s p Void o a -> s p i o a Source #
beforeStep :: Monoid p => Automaton p i o a -> Either (Automaton p v o a) (Automaton p i o a) Source #
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 #
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 :: Monoid p => 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. The removal
is visible to getCount
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.