parsley-core-1.4.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityunstable
Safe HaskellNone
LanguageHaskell2010

Parsley.Internal

Description

This module exposes all of the required functionality found in the internals of the library out to the user API.

Since: 0.1.0.0

Synopsis

Documentation

data Reg (r :: Type) a Source #

This is an opaque representation of a parsing register. It cannot be manipulated as a user, and the type parameter r is used to ensure that it cannot leak out of the scope it has been created in. It is the abstracted representation of a runtime storage location.

Since: 0.1.0.0

conditional Source #

Arguments

:: ParserOps rep 
=> [(rep (a -> Bool), Parser b)]

A list of predicates and their outcomes

-> Parser a

A parser whose result is used to choose an outcome

-> Parser b

A parser who will be executed if no predicates succeed

-> Parser b 

conditional fqs p def first parses p, then it will try each of the predicates in fqs in turn until one of them returns True. The corresponding parser for the first predicate that succeeded is then executes, or if none of the predicates succeeded then the def parser is executed.

Since: 0.1.0.0

pure :: ParserOps rep => rep a -> Parser a Source #

Lift a value into the parser world without consuming input or having any other effect.

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

(<*>) :: Parser (a -> b) -> Parser a -> Parser b infixl 4 Source #

Sequential application of one parser's result to another's. The parsers must both succeed, one after the other to combine their results. If either parser fails then the combinator will fail.

Since: 0.1.0.0

(<*) :: Parser a -> Parser b -> Parser a infixl 4 Source #

Sequence two parsers, keeping the result of the second and discarding the result of the first.

Since: 0.1.0.0

(*>) :: Parser a -> Parser b -> Parser b infixl 4 Source #

Sequence two parsers, keeping the result of the first and discarding the result of the second.

Since: 0.1.0.0

empty :: Parser a Source #

This combinator always fails.

Since: 0.1.0.0

(<|>) :: Parser a -> Parser a -> Parser a infixr 3 Source #

This combinator implements branching within a parser. It is left-biased, so that if the first branch succeeds, the second will not be attempted. In accordance with parsec semantics, if the first branch failed having consumed input the second branch cannot be taken. (see try)

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

branch Source #

Arguments

:: Parser (Either a b)

The first parser to execute

-> Parser (a -> c)

The parser to execute if the first returned a Left

-> Parser (b -> c)

The parser to execute if the first returned a Right

-> Parser c 

One of the core Selective operations. The behaviour of branch p l r is to first to parse p, if it fails then the combinator fails. If p succeeded then if its result is a Left, then the parser l is executed and applied to the result of p, otherwise r is executed and applied to the right from a Right.

Crucially, only one of l or r will be executed on p's success.

Since: 0.1.0.0

chainPre :: Parser (a -> a) -> Parser a -> Parser a Source #

This combinator parses repeated applications of an operator to a single final operand. This is primarily used to parse prefix operators in expressions.

Since: 0.1.0.0

chainPost :: Parser a -> Parser (a -> a) -> Parser a Source #

This combinator parses repeated applications of an operator to a single initial operand. This is primarily used to parse postfix operators in expressions.

Since: 0.1.0.0

newRegister Source #

Arguments

:: Parser a

Parser with which to initialise the register

-> (forall r. Reg r a -> Parser b)

Used to generate the second parser to execute

-> Parser b 

Creates a new register initialised with the value obtained from parsing the first argument. This register is provided to the second argument, a function that generates a parser depending on operations derived from the register. This parser is then performed.

Note: The rank-2 type here serves a similar purpose to that in the ST monad. It prevents the register from leaking outside of the scope of the function, safely encapsulating the stateful effect of the register.

Since: 0.1.0.0

get :: Reg r a -> Parser a Source #

Fetches a value from a register and returns it as its result.

Since: 0.1.0.0

put :: Reg r a -> Parser a -> Parser () Source #

Puts the result of the given parser into the given register. The old value in the register will be lost.

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

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

Minimal complete definition

makeQ, _val, _code

Methods

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

_val :: q a -> a Source #

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

Instances details
Quapplicative WQ Source #

This instance is used to manipulate values of WQ.

Since: 0.1.0.0

Instance details

Defined in Parsley.Internal.Common.Utils

Methods

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

_val :: WQ a -> a Source #

_code :: WQ a -> Code a Source #

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

Quapplicative Defunc Source #

This instance is used to manipulate values of Defunc.

Since: 0.1.0.0

Instance details

Defined in Parsley.Internal.Core.Defunc

Methods

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

_val :: Defunc a -> a Source #

_code :: Defunc a -> Code a Source #

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

data WQ a Source #

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

Instances

Instances details
Quapplicative WQ Source #

This instance is used to manipulate values of WQ.

Since: 0.1.0.0

Instance details

Defined in Parsley.Internal.Common.Utils

Methods

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

_val :: WQ a -> a Source #

_code :: WQ a -> Code a Source #

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

ParserOps WQ 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.Internal.Core.Primitives

Methods

pure :: WQ a -> Parser a Source #

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

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

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

class Trace where Source #

Used to produce debug output within parsley.

Since: 0.1.0.0

Methods

trace :: String -> a -> a Source #

Print a string to the console.

Instances

Instances details
Trace Source #

This instance, when in scope, will enable additional debug output from the Parsley compilation process. It will always superscede the default instance defined in Parsley.

Since: 0.1.0.0

Instance details

Defined in Parsley.Internal.Verbose

Methods

trace :: String -> a -> a Source #

compile Source #

Arguments

:: forall compiled a. Trace 
=> Parser a

The parser to compile.

-> (forall x. Maybe (MVar x) -> Fix Combinator x -> Set SomeΣVar -> IMVar -> IΣVar -> compiled x)

How to generate a compiled value with the distilled information.

-> (compiled a, DMap MVar compiled)

The compiled top-level and all of the bindings.

Given a user's parser, this will analyse it, extract bindings and then compile them with a given function provided with the information that has been distilled about each binding. Returns all the prepared bindings along with the top-level definition.

Since: 1.0.0.0

class (InputPrep input, Ops input) => Input input Source #

This class is exposed to parsley itself and is used to denote which types may be used as input for a parser.

Since: 0.1.0.0

Instances

Instances details
Input ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input ByteString Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input [Char] Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

eval :: forall input a. (Input input, Trace) => Code input -> (LetBinding input a a, DMap MVar (LetBinding input a)) -> Code (Maybe a) Source #

This function is exposed to parsley itself and is used to generate the Haskell code for a parser.

Since: 0.1.0.0

codeGen Source #

Arguments

:: Trace 
=> Maybe (MVar x)

The name of the parser, if it exists.

-> Fix Combinator x

The definition of the parser.

-> Set SomeΣVar

The free registers it requires to run.

-> IMVar

The binding identifier to start name generation from.

-> IΣVar

The register identifier to start name generation from.

-> LetBinding o a x 

Translates a parser represented with combinators into its machine representation.

Since: 1.0.0.0