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

Parsley.Defunctionalized

Description

This module exports the Defunc type and associated patterns. These are by no means required to use Parsley, however they can serve as useful shortcuts to their regular Haskell equivalents. As they are in datatype form, they are inspectable by the internal Parsley machinery, which may improve optimisation opportunities or code generation.

Since: 0.1.0.0

Synopsis

Documentation

data Defunc a where #

This datatype is useful for providing an inspectable representation of common Haskell functions. These can be provided in place of WQ to any combinator that requires it. The only difference is that the Parsley compiler is able to manipulate and match on the constructors, which might lead to optimisations. They can also be more convenient than constructing the WQ object itself:

ID ~= WQ id [||id||]
APP_H f x ~= WQ (f x) [||f x||]

Since: parsley-core-0.1.0.0

Constructors

ID :: forall a1. Defunc (a1 -> a1)

Corresponds to the standard id function

COMPOSE :: forall b c a1. Defunc ((b -> c) -> (a1 -> b) -> a1 -> c)

Corresponds to the standard (.) function applied to no arguments.

FLIP :: forall a1 b c. Defunc ((a1 -> b -> c) -> b -> a1 -> c)

Corresponds to the standard flip function applied to no arguments.

APP_H :: forall a1 a. Defunc (a1 -> a) -> Defunc a1 -> Defunc a

Corresponds to function application of two other Defunc values.

EQ_H :: forall a1. Eq a1 => Defunc a1 -> Defunc (a1 -> Bool)

Corresponds to the partially applied (== x) for some Defunc value x.

LIFTED :: forall a. (Show a, Lift a, Typeable a) => a -> Defunc a

Represents a liftable, showable, typable value.

CONS :: forall a1. Defunc (a1 -> [a1] -> [a1])

Represents the standard (:) function applied to no arguments.

CONST :: forall a1 b. Defunc (a1 -> b -> a1)

Represents the standard const function applied to no arguments.

EMPTY :: forall a1. Defunc [a1]

Represents the empty list [].

BLACK :: forall a. WQ a -> Defunc a

Wraps up any value of type WQ.

RANGES

Designed to be a specialised form of character predicate: is a character within some given ranges (which are inclusive at both ends).

Since: parsley-core-2.0.0.0

Fields

  • :: Bool

    Does the range test for membership (True) or no membership (False).

  • -> [(Char, Char)]

    List of ranges of the form (l, u): l and u are inclusive to the range.

  • -> Defunc (Char -> Bool)
     
IF_S :: forall a. Defunc Bool -> Defunc a -> Defunc a -> Defunc a

Represents the regular Haskell if syntax.

Since: parsley-core-0.1.1.0

LAM_S :: forall a1 b. (Defunc a1 -> Defunc b) -> Defunc (a1 -> b)

Represents a Haskell lambda abstraction.

Since: parsley-core-0.1.1.0

LET_S :: forall a1 a. Defunc a1 -> (Defunc a1 -> Defunc a) -> Defunc a

Represents a Haskell let binding.

Since: parsley-core-0.1.1.0

Instances

Instances details
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 #

Show (Defunc a) 
Instance details

Defined in Parsley.Internal.Core.Defunc

Methods

showsPrec :: Int -> Defunc a -> ShowS #

show :: Defunc a -> String #

showList :: [Defunc a] -> ShowS #

pattern UNIT :: Defunc () #

This pattern represents the unit value ().

Since: parsley-core-0.1.0.0

pattern FLIP_CONST :: forall x a b. () => forall. x ~ (a -> b -> b) => Defunc x #

Represents the flipped standard const function applied to no arguments.

Since: parsley-core-0.1.0.0

pattern FLIP_H :: forall y x a b c. () => forall. (x -> y) ~ ((a -> b -> c) -> b -> a -> c) => Defunc x -> Defunc y #

This pattern corresponds to the standard flip function applied to a single argument.

Since: parsley-core-0.1.0.0

pattern COMPOSE_H :: forall z x y b c a. () => forall. (x -> y -> z) ~ ((b -> c) -> (a -> b) -> a -> c) => Defunc x -> Defunc y -> Defunc z #

This pattern represents fully applied composition of two Defunc values.

Since: parsley-core-0.1.0.0