parsley-2.0.0.1: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilitystable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Parsley

Description

This module contains the core execution functions parse 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

Documentation

parse Source #

Arguments

:: (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 = $$(parse 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: 2.0.0.0

parseFromFile Source #

Arguments

:: Trace 
=> Parser a

The parser to be compiled

-> Code (FilePath -> IO (Maybe a))

The generated parsing function

This function generates a function that reads input from a file and parses it. The input files contents are treated as Text.

See parse for more information.

Since: 0.1.0.0

data Parser a #

The opaque datatype that represents parsers.

Since: parsley-core-0.1.0.0

class ParserOps rep Source #

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

Minimal complete definition

pure, satisfy, conditional

Instances

Instances details
ParserOps Defunc 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

Instance details

Defined in Parsley.ParserOps

Methods

pure :: Defunc a -> Parser a Source #

satisfy :: Defunc (Char -> Bool) -> Parser Char Source #

conditional :: [(Defunc (a -> Bool), Parser b)] -> Parser a -> Parser b -> Parser b Source #

x ~ WQ => ParserOps x Source #

This is the default representation used for user-level functions and values: plain old code.

Since: 0.1.0.0

Instance details

Defined in Parsley.ParserOps

Methods

pure :: x a -> Parser a Source #

satisfy :: x (Char -> Bool) -> Parser Char Source #

conditional :: [(x (a -> Bool), Parser b)] -> Parser a -> Parser b -> Parser b Source #

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

satisfy Source #

Arguments

:: 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

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: 2.0.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: 2.0.0.0

item :: Parser Char Source #

Reads any single character. This combinator will only fail if there is no more input remaining. The parsed character is returned.

Since: 2.0.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

debug Source #

Arguments

:: 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

type Code (a :: TYPE r) = Code Q a #

A type alias for typed template haskell code, which represents the Haskell AST for a given value.

Since: parsley-core-0.1.0.0

data WQ a #

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: parsley-core-0.1.0.0

Instances

Instances details
Quapplicative WQ

This instance is used to manipulate values of WQ.

Since: parsley-core-0.1.0.0

Instance details

Defined in Parsley.Internal.Common.Utils

Methods

makeQ :: a -> Code a -> WQ a #

_val :: WQ a -> a #

_code :: WQ a -> Code a #

(>*<) :: WQ (a -> b) -> WQ a -> WQ b #

class Quapplicative (q :: TYPE LiftedRep -> Type) where #

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: parsley-core-0.1.0.0

Minimal complete definition

makeQ, _val, _code

Methods

makeQ :: a -> Code a -> q a #

Combines a value with its representation to build one of the representation types.

Since: parsley-core-0.1.0.0

_val :: q a -> a #

Extracts the regular value out of the representation.

Since: parsley-core-0.1.0.0

_code :: q a -> Code a #

Extracts the representation of the value as code.

Since: parsley-core-0.1.0.0

(>*<) :: q (a -> b) -> q a -> q b infixl 9 #

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: parsley-core-0.1.0.0

Instances

Instances details
Quapplicative WQ

This instance is used to manipulate values of WQ.

Since: parsley-core-0.1.0.0

Instance details

Defined in Parsley.Internal.Common.Utils

Methods

makeQ :: a -> Code a -> WQ a #

_val :: WQ a -> a #

_code :: WQ a -> Code a #

(>*<) :: WQ (a -> b) -> WQ a -> WQ b #

Quapplicative Defunc

This instance is used to manipulate values of Defunc.

Since: parsley-core-0.1.0.0

Instance details

Defined in Parsley.Internal.Core.Defunc

Methods

makeQ :: a -> Code a -> Defunc a #

_val :: Defunc a -> a #

_code :: Defunc a -> Code a #

(>*<) :: Defunc (a -> b) -> Defunc a -> Defunc b #

Orphan instances

Trace Source #

The default instance for Trace, which disables all debugging output about the parser compilation process. If Parsley.Internal.Verbose is imported, this instance will be supersceded.

Since: 0.1.0.0

Instance details

Methods

trace :: String -> a -> a #