Copyright | Jeremy List |
---|---|
License | BSD-3 |
Maintainer | quick.dudley@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Phase p i o a
- data Automaton p i o a
- data Position = Position !Int !Int
- class Standardized r a where
- (>>#) :: (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
- (<?>) :: [Char] -> Phase p i o a -> Phase p i o a
- ($#$) :: (PhaserType s, Monoid p) => s p b c x -> (c -> t) -> s p b t x
- parse :: PhaserType s => s Position i o a -> [i] -> Either [(Position, [String])] [a]
- parse_ :: (Monoid p, PhaserType s) => p -> s p i o a -> [i] -> Either [(p, [String])] [a]
- parseFile :: PhaserType s => s Position Word8 o a -> FilePath -> IO (Either [(Position, [String])] [a])
- parseFile_ :: (Monoid p, PhaserType s) => p -> s p Word8 o a -> FilePath -> IO (Either [(p, [String])] [a])
- parseHandle :: PhaserType s => s Position Word8 o a -> Handle -> IO (Either [(Position, [String])] [a])
- parseHandle_ :: (Monoid p, PhaserType s) => p -> s p Word8 o a -> Handle -> IO (Either [(p, [String])] [a])
- get :: Phase p i o i
- count :: p -> Phase p i o ()
- yield :: o -> Phase p i o ()
- put1 :: Monoid p => i -> Phase p i o ()
- put :: Monoid p => [i] -> Phase p i o ()
- run :: Monoid p => Automaton p i o a -> [i] -> 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]
- satisfy :: Monoid p => (i -> Bool) -> Phase p i o i
- match :: (Eq i, Monoid p) => i -> Phase p i o i
- char :: Monoid p => Char -> Phase p Char o Char
- iChar :: Monoid p => Char -> Phase p Char o Char
- string :: (Eq i, Monoid p) => [i] -> Phase p i o [i]
- iString :: Monoid p => String -> Phase p Char o String
- integer :: (Num a, Monoid p) => Phase p Char o a
- decimal :: (Fractional a, Monoid p) => Phase p Char o a
- scientificNotation :: (Fractional a, Monoid p) => Phase p Char o a
- sepBy :: Monoid p => Phase p i o a -> Phase p i o s -> Phase p i o [a]
- munch :: Monoid p => (i -> Bool) -> Phase p i o [i]
- munch1 :: Monoid p => (i -> Bool) -> Phase p i o [i]
- trackPosition :: Phase Position Char Char ()
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.
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 # | |
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 data type for describing a position in a text file. Constructor arguments are row number and column number.
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).
Instances
(>>#) :: (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.
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
.
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
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.
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.