Copyright | Jeremy List |
---|---|
License | BSD-3 |
Maintainer | quick.dudley@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Position = Position !Int !Int
- class PhaserType s where
- class Standardized r a where
- data Trie c a
- newTrie :: Ord c => [c] -> a -> Trie c a
- fromTrie :: (Monoid p, PhaserType s, Ord c) => Trie c a -> s p c o 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
- (<#>) :: (PhaserType d, PhaserType s, Monoid p) => s p b c (a -> z) -> d p c t a -> Automaton p b t z
- integerDecimal :: (Num a, Monoid p) => Phase p Char o a
- positiveIntegerDecimal :: (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
- directHex :: (Num a, Monoid p) => Phase p Char o a
- hex :: (Num a, Monoid p) => Phase p Char o a
- positiveInteger :: (Num a, Monoid p) => Phase p Char o a
- integer :: (Num a, Monoid p) => Phase p Char o a
- countChar :: Phase Position i o ()
- countLine :: Phase Position i o ()
- trackPosition :: Phase Position Char Char ()
- normalizeNewlines :: Monoid p => Phase p Char Char ()
- parse :: PhaserType s => s Position i o a -> [i] -> Either [(Position, [String])] [a]
- sepBy :: Monoid p => Phase p i o a -> Phase p i o s -> Phase p i o [a]
- sepBy1 :: 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]
- parseFile :: PhaserType s => s Position Word8 o a -> FilePath -> IO (Either [(Position, [String])] [a])
- parseHandle :: PhaserType s => s Position Word8 o a -> Handle -> IO (Either [(Position, [String])] [a])
- latin1 :: Monoid p => Phase p Word8 Char ()
Documentation
A data type for describing a position in a text file. Constructor arguments are row number and column number.
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 # |
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
Tries in this module can be used for creating more efficient parsers when several of the recognized strings begin with the same few characters
newTrie :: Ord c => [c] -> a -> Trie c a Source #
Create a trie which maps a single string to an object. Analogous to
singleton
.
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.
(<#>) :: (PhaserType d, PhaserType s, Monoid p) => s p b c (a -> z) -> d p c t a -> Automaton p b t z infixl 5 Source #
positiveIntegerDecimal :: (Num a, Monoid p) => Phase p Char o a Source #
Parse a standard positive base 10 integer
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.
directHex :: (Num a, Monoid p) => Phase p Char o a Source #
Take some hexadecimal digits and parse a number from hexadecimal
positiveInteger :: (Num a, Monoid p) => Phase p Char o a Source #
Parse a positive integer from either decimal or hexadecimal format
integer :: (Num a, Monoid p) => Phase p Char o a Source #
Parse a number either from decimal digits or from hexadecimal prefixed with "0x"
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.
normalizeNewlines :: Monoid p => Phase p Char Char () Source #
Converts all line separators into Unix format.
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.
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.
sepBy1 :: Monoid p => Phase p i o a -> Phase p i o s -> Phase p i o [a] Source #
sepBy1 p sep parses one 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))
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.
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.