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

Parsley.Internal.Core.Defunc

Description

This module contains the infrastructure and definitions of defunctionalised terms that can be used by the user and the frontend.

Since: 1.0.0.0

Synopsis

Documentation

data Defunc a where Source #

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

Constructors

ID :: Defunc (a -> a)

Corresponds to the standard id function

COMPOSE :: Defunc ((b -> c) -> (a -> b) -> a -> c)

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

FLIP :: Defunc ((a -> b -> c) -> b -> a -> c)

Corresponds to the standard flip function applied to no arguments.

APP_H :: Defunc (a -> b) -> Defunc a -> Defunc b

Corresponds to function application of two other Defunc values.

EQ_H :: Eq a => Defunc a -> Defunc (a -> Bool)

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

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

Represents a liftable, showable value.

CONS :: Defunc (a -> [a] -> [a])

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

CONST :: Defunc (a -> b -> a)

Represents the standard const function applied to no arguments.

EMPTY :: Defunc [a]

Represents the empty list [].

BLACK :: WQ a -> Defunc a

Wraps up any value of type WQ.

IF_S :: Defunc Bool -> Defunc a -> Defunc a -> Defunc a

Represents the regular Haskell if syntax.

Since: 0.1.1.0

LAM_S :: (Defunc a -> Defunc b) -> Defunc (a -> b)

Represents a Haskell lambda abstraction.

Since: 0.1.1.0

LET_S :: Defunc a -> (Defunc a -> Defunc b) -> Defunc b

Represents a Haskell let binding.

Since: 0.1.1.0

Instances

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

Show (Defunc a) Source # 
Instance details

Defined in Parsley.Internal.Core.Defunc

Methods

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

show :: Defunc a -> String #

showList :: [Defunc a] -> ShowS #

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

This pattern represents fully applied composition of two Defunc values.

Since: 0.1.0.0

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

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

Since: 0.1.0.0

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

Represents the flipped standard const function applied to no arguments.

Since: 0.1.0.0

pattern UNIT :: Defunc () Source #

This pattern represents the unit value ().

Since: 0.1.0.0

lamTerm :: Defunc a -> Lam a Source #

Converts a Defunc value into an equivalent Lam value, discarding the inspectivity of functions.

Since: 1.0.1.0

lamTermBool :: Defunc (a -> Bool) -> Lam (a -> Bool) Source #

Specialised conversion for functions returning Bool. This will go as soon as Defunc has a Typeable constraint in parsley 2.

Since: 1.0.1.0