License | BSD-3-Clause |
---|---|
Maintainer | Jamie Willis |
Stability | stable |
Safe Haskell | None |
Language | Haskell2010 |
This module contains the core execution functions runParser
and parseFromFile
.
It exports the Parser
type, as well as the ParserOps
typeclass, which may be needed
as a constraint to create more general combinators. It also exports several of the more
important modules and functionality in particular the core set of combinators.
Since: 0.1.0.0
Synopsis
- runParser :: (Trace, Input input) => Parser a -> Code (input -> Maybe a)
- parseFromFile :: Trace => Parser a -> Code (FilePath -> IO (Maybe a))
- data Parser a
- class ParserOps rep
- debug :: String -> Parser a -> Parser a
- module Parsley.Applicative
- module Parsley.Alternative
- module Parsley.Selective
- satisfy :: ParserOps rep => rep (Char -> Bool) -> Parser Char
- lookAhead :: Parser a -> Parser a
- notFollowedBy :: Parser a -> Parser ()
- try :: Parser a -> Parser a
- string :: String -> Parser String
- char :: Char -> Parser Char
- item :: Parser Char
- many :: Parser a -> Parser [a]
- some :: Parser a -> Parser [a]
- class Quapplicative q where
- data WQ a
- type Code a = Q (TExp a)
Documentation
:: (Trace, Input input) | |
=> Parser a | The parser to be compiled |
-> Code (input -> Maybe a) | The generated parsing function |
The standard way to compile a parser, it returns Code
, which means
that it must be spliced into a function definition to produce a
function of type input -> Maybe a
for a chosen input type. As an example:
In Parser.hs
:
helloParsley :: Parser String helloParsley = string "hello Parsley!"
In Main.hs
:
parseHelloParsley :: String -> Maybe String parseHelloParsley = $$(runParser helloParsley)
Note that the definition of the parser must be in a separate module to
the splice ($$
).
See Input
for what the valid input types for Parsley are.
The Trace
instance is used to enable verbose debugging output for
the compilation pipeline when Parsley.Internal.Verbose is imported.
Since: 0.1.0.0
This typeclass is used to allow abstraction of the representation of user-level functions. See the instances for information on what these representations are. This may be required as a constraint on custom built combinators that make use of one of the minimal required methods of this class.
Since: 0.1.0.0
Instances
x ~ Defunc => ParserOps x Source # | This is used to allow defunctionalised versions of many standard Haskell functions to be used directly as an argument to relevant combinators. Since: 0.1.0.0 |
ParserOps WQ Source # | This is the default representation used for user-level functions and values: plain old code. Since: 0.1.0.0 |
:: String | The name that identifies the wrapped parser in the debug trace |
-> Parser a | The parser to track during execution |
-> Parser a |
This combinator can be used to debug parsers that have gone wrong. Simply
wrap a parser with debug name
and when that parser is executed it will
print a debug trace on entry and exit along with the current context of the
input.
Since: 0.1.0.0
module Parsley.Applicative
module Parsley.Alternative
module Parsley.Selective
:: ParserOps rep | |
=> rep (Char -> Bool) | The predicate that a character must satisfy to be parsed |
-> Parser Char | A parser that matches a single character matching the predicate |
Attempts to read a single character matching the provided predicate. If it succeeds, the character will be returned and consumed, otherwise the parser will fail having consumed no input.
Since: 0.1.0.0
lookAhead :: Parser a -> Parser a Source #
This combinator will attempt to parse a given parser. If it succeeds, the result is returned without having consumed any input. If it fails, however, any consumed input remains consumed.
Since: 0.1.0.0
notFollowedBy :: Parser a -> Parser () Source #
This combinator will ensure that a given parser fails. If the parser does fail, a ()
is returned
and no input is consumed. If the parser succeeded, then this combinator will fail, however it will
not consume any input.
Since: 0.1.0.0
try :: Parser a -> Parser a Source #
This combinator allows a parser to backtrack on failure, which is to say that it will
not have consumed any input if it were to fail. This is important since parsec
semantics demand
that the second branch of (
can only be taken if the first did not consume input on failure.<|>
)
Excessive use of try
will reduce the efficiency of the parser and effect the generated error
messages. It should only be used in one of two circumstances:
- When two branches of a parser share a common leading prefix (in which case, it is often better to try and factor this out).
- When a parser needs to be executed atomically (for example, tokens).
Since: 0.1.0.0
string :: String -> Parser String Source #
This combinator will attempt match a given string. If the parser fails midway through, this combinator will fail having consumed input. On success, the string itself is returned and input will be consumed.
Since: 0.1.0.0
char :: Char -> Parser Char Source #
This combinator will attempt to match a given character. If that character is the next input token, the parser succeeds and the character is returned. Otherwise, the combinator will fail having not consumed any input.
Since: 0.1.0.0
Reads any single character. This combinator will only fail if there is no more input remaining. The parsed character is returned.
Since: 0.1.0.0
many :: Parser a -> Parser [a] Source #
Attempts to parse the given parser zero or more times, collecting all of the successful results
into a list. Same as manyN 0
Since: 0.1.0.0
some :: Parser a -> Parser [a] Source #
Attempts to parse the given parser one or more times, collecting all of the successful results
into a list. Same as manyN 1
Since: 0.1.0.0
class Quapplicative q where Source #
This class is used to manipulate the representations of both user-land values and defunctionalised representations. It can be used to construct these values as well as extract their underlying value and code representation on demand.
It is named after the Applicative
class, with the Q
standing for "code". The (
operator
is analogous to >*<
)(<*>)
and makeQ
analogous to pure
.
Since: 0.1.0.0
makeQ :: a -> Code a -> q a Source #
Combines a value with its representation to build one of the representation types.
Since: 0.1.0.0
Extracts the regular value out of the representation.
Since: 0.1.0.0
_code :: q a -> Code a Source #
Extracts the representation of the value as code.
Since: 0.1.0.0
(>*<) :: q (a -> b) -> q a -> q b infixl 9 Source #
Pronounced "quapp", this can be used to combine the code of a function with the code of a value.
const5 = makeQ const [||const||] >*< makeQ 5 [||5||]
is the same as saying
const5 = makeQ (const 5) [||const 5||]
It is more idiomatically found as the output to the IdiomsPlugin
.
Since: 0.1.0.0
Instances
Quapplicative WQ Source # | This instance is used to manipulate values of Since: 0.1.0.0 |
Quapplicative Defunc Source # | This instance is used to manipulate values of Since: 0.1.0.0 |
Pronounced "with code", this datatype is the representation for user-land values. It pairs
a value up with its representation as Haskell Code
. It should be manipulated using
Quapplicative
.
Since: 0.1.0.0
type Code a = Q (TExp a) Source #
A type alias for typed template haskell code, which represents the Haskell AST for a given value.
Since: 0.1.0.0