Copyright | Jeremy List |
---|---|
License | BSD-3 |
Maintainer | quick.dudley@gmail.com |
Safe Haskell | None |
Language | Haskell2010 |
- data Phase p i o a
- data Automaton p i o a
- data Position = Position !Int !Int
- (>>#) :: Link s d l => s p b c x -> d p c t a -> l p b t a
- (>#>) :: ((p0 -> p0) -> p -> p) -> Phase p0 i o a -> Phase p i o a
- (<?>) :: [Char] -> Phase p i o a -> Phase p i o a
- parse :: Phase Position i o a -> [i] -> Either [(Position, [String])] [a]
- parse_ :: p -> Phase p i o a -> [i] -> Either [(p, [String])] [a]
- get :: Phase p i o i
- count :: (p -> p) -> Phase p i o ()
- yield :: o -> Phase p i o ()
- put1 :: i -> Phase p i o ()
- put :: [i] -> Phase p i o ()
- run :: Automaton p i o a -> [i] -> Automaton p i o a
- step :: Automaton p i o a -> i -> Automaton p i o a
- extract :: p -> Automaton p i o a -> Either [(p, [String])] [a]
- satisfy :: (i -> Bool) -> Phase p i o i
- match :: Eq i => i -> Phase p i o i
- char :: Char -> Phase p Char o Char
- iChar :: Char -> Phase p Char o Char
- string :: Eq i => [i] -> Phase p i o [i]
- iString :: String -> Phase p Char o String
- integer :: Num a => Phase p Char o a
- decimal :: Fractional a => Phase p Char o a
- sepBy :: Phase p i o a -> Phase p i o s -> Phase p i o [a]
- munch :: (i -> Bool) -> Phase p i o [i]
- munch1 :: (i -> Bool) -> Phase p i o [i]
Documentation
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.
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.
A data type for describing a position in a text file. Constructor arguments are row number and column number.
(>>#) :: Link s d l => s p b c x -> d p c t a -> l p b t a 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.
(>#>) :: ((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.
(<?>) :: [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
parse :: Phase 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_ :: p -> Phase p i o a -> [i] -> Either [(p, [String])] [a] Source #
Use a Phase
value similarly to a parser.
put1 :: i -> Phase p i o () Source #
Insert one value back into the input. May be used for implementing lookahead
run :: Automaton p i o a -> [i] -> Automaton p i o a Source #
Pass a list of input values 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.
satisfy :: (i -> Bool) -> Phase p i o i Source #
Consume one input, return it if it matches the predicate, otherwise fail.
match :: Eq i => i -> Phase p i o i Source #
Consume one input, if it's equal to the parameter then return it, otherwise fail.
integer :: Num a => Phase p Char o a Source #
Parse a number either from decimal digits or from hexadecimal prefixed with "0x"
sepBy :: 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.