parsley-core-2.3.0.0: A fast parser combinator library backed by Typed Template Haskell
LicenseBSD-3-Clause
MaintainerJamie Willis
Stabilityunstable
Safe HaskellSafe-Inferred
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 :: [(Defunc (a -> Bool), Parser b)] -> Parser a -> Parser b -> Parser b Source #

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

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

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

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

branch :: Parser (Either a b) -> Parser (a -> c) -> Parser (b -> c) -> Parser c Source #

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

newRegister :: Parser a -> (forall r. Reg r a -> Parser b) -> Parser b Source #

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

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

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 #

type Code a = Code Q 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 #

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 CharList Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input Stream Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input Text16 Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input Text Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input String Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

Input (UArray Int Char) Source # 
Instance details

Defined in Parsley.Internal.Backend.Machine

parse :: (Trace, Input input) => Parser a -> Code (input -> Maybe a) Source #

parseWithOpts :: (Trace, Input input) => Flags -> Parser a -> Code (input -> Maybe a) Source #