code-conjure-0.5.0: synthesize Haskell functions out of partial definitions
Copyright(c) 2021 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Conjure.Conjurable

Description

This module is part of Conjure.

This defines the Conjurable typeclass and utilities involving it.

You are probably better off importing Conjure.

Synopsis

Documentation

type Reification1 = (Expr, Maybe Expr, Maybe [[Expr]], [String], Bool, Expr) Source #

Single reification of some functions over a type as Exprs.

This is a sixtuple, in order:

  1. a hole encoded as an Expr;
  2. the == function encoded as an Expr when available;
  3. tiers of enumerated test values encoded as Exprs when available;
  4. infinite list of potential variable names;
  5. boolean indicating whether the type is atomic;
  6. the conjureSize function encoded as an Expr.

type Reification = [Reification1] -> [Reification1] Source #

A reification over a collection of types.

Represented as a transformation of a list to a list.

class (Typeable a, Name a) => Conjurable a where Source #

Class of Conjurable types. Functions are Conjurable if all their arguments are Conjurable, Listable and Showable.

For atomic types that are Listable, instances are defined as:

instance Conjurable Atomic where
  conjureTiers  =  reifyTiers

For atomic types that are both Listable and Eq, instances are defined as:

instance Conjurable Atomic where
  conjureTiers     =  reifyTiers
  conjureEquality  =  reifyEquality

For types with subtypes, instances are defined as:

instance Conjurable Composite where
  conjureTiers     =  reifyTiers
  conjureEquality  =  reifyEquality
  conjureSubTypes x  =  conjureType y
                     .  conjureType z
                     .  conjureType w
    where
    (Composite ... y ... z ... w ...)  =  x

Above x, y, z and w are just proxies. The Proxy type was avoided for backwards compatibility.

Please see the source code of Conjure.Conjurable for more examples.

(cf. reifyTiers, reifyEquality, conjureType)

Minimal complete definition

conjureExpress

Methods

conjureArgumentHoles :: a -> [Expr] Source #

conjureEquality :: a -> Maybe Expr Source #

Returns Just the == function encoded as an Expr when available or Nothing otherwise.

Use reifyEquality when defining this.

conjureTiers :: a -> Maybe [[Expr]] Source #

Returns Just tiers of values encoded as Exprs when possible or Nothing otherwise.

Use reifyTiers when defining this.

conjureSubTypes :: a -> Reification Source #

conjureIf :: a -> Expr Source #

Returns an if-function encoded as an Expr.

conjureCases :: a -> [Expr] Source #

Returns a top-level case breakdown.

conjureArgumentCases :: a -> [[Expr]] Source #

conjureSize :: a -> Int Source #

Returns the (recursive) size of the given value.

conjureExpress :: a -> Expr -> Expr Source #

Returns a function that deeply reencodes an expression when possible. (id when not available.)

Use reifyExpress when defining this.

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a Source #

Instances

Instances details
Conjurable Bool Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Char Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Double Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Float Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int8 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int16 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int32 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Int64 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Integer Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Ordering Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word8 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word16 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word32 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable Word64 Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable () Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable A Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable B Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable C Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable D Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable E Source # 
Instance details

Defined in Conjure.Conjurable

Conjurable F Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Express a, Show a) => Conjurable [a] Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a, Express a) => Conjurable (Maybe a) Source # 
Instance details

Defined in Conjure.Conjurable

(Integral a, Conjurable a, Listable a, Show a, Eq a, Express a) => Conjurable (Ratio a) Source # 
Instance details

Defined in Conjure.Conjurable

(RealFloat a, Conjurable a, Listable a, Show a, Eq a, Express a) => Conjurable (Complex a) Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Conjurable b) => Conjurable (a -> b) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a -> b) -> [Expr] Source #

conjureEquality :: (a -> b) -> Maybe Expr Source #

conjureTiers :: (a -> b) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a -> b) -> Reification Source #

conjureIf :: (a -> b) -> Expr Source #

conjureCases :: (a -> b) -> [Expr] Source #

conjureArgumentCases :: (a -> b) -> [[Expr]] Source #

conjureSize :: (a -> b) -> Int Source #

conjureExpress :: (a -> b) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a -> b) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b) => Conjurable (Either a b) Source # 
Instance details

Defined in Conjure.Conjurable

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b) => Conjurable (a, b) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b) -> [Expr] Source #

conjureEquality :: (a, b) -> Maybe Expr Source #

conjureTiers :: (a, b) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b) -> Reification Source #

conjureIf :: (a, b) -> Expr Source #

conjureCases :: (a, b) -> [Expr] Source #

conjureArgumentCases :: (a, b) -> [[Expr]] Source #

conjureSize :: (a, b) -> Int Source #

conjureExpress :: (a, b) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c) => Conjurable (a, b, c) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c) -> [Expr] Source #

conjureEquality :: (a, b, c) -> Maybe Expr Source #

conjureTiers :: (a, b, c) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c) -> Reification Source #

conjureIf :: (a, b, c) -> Expr Source #

conjureCases :: (a, b, c) -> [Expr] Source #

conjureArgumentCases :: (a, b, c) -> [[Expr]] Source #

conjureSize :: (a, b, c) -> Int Source #

conjureExpress :: (a, b, c) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d) => Conjurable (a, b, c, d) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d) -> [Expr] Source #

conjureEquality :: (a, b, c, d) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d) -> Reification Source #

conjureIf :: (a, b, c, d) -> Expr Source #

conjureCases :: (a, b, c, d) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d) -> [[Expr]] Source #

conjureSize :: (a, b, c, d) -> Int Source #

conjureExpress :: (a, b, c, d) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e) => Conjurable (a, b, c, d, e) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d, e) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d, e) -> Reification Source #

conjureIf :: (a, b, c, d, e) -> Expr Source #

conjureCases :: (a, b, c, d, e) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d, e) -> [[Expr]] Source #

conjureSize :: (a, b, c, d, e) -> Int Source #

conjureExpress :: (a, b, c, d, e) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e, Conjurable f, Listable f, Show f, Express f) => Conjurable (a, b, c, d, e, f) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e, f) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e, f) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d, e, f) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d, e, f) -> Reification Source #

conjureIf :: (a, b, c, d, e, f) -> Expr Source #

conjureCases :: (a, b, c, d, e, f) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d, e, f) -> [[Expr]] Source #

conjureSize :: (a, b, c, d, e, f) -> Int Source #

conjureExpress :: (a, b, c, d, e, f) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f) Source #

(Conjurable a, Listable a, Show a, Express a, Conjurable b, Listable b, Show b, Express b, Conjurable c, Listable c, Show c, Express c, Conjurable d, Listable d, Show d, Express d, Conjurable e, Listable e, Show e, Express e, Conjurable f, Listable f, Show f, Express f, Conjurable g, Listable g, Show g, Express g) => Conjurable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Conjure.Conjurable

Methods

conjureArgumentHoles :: (a, b, c, d, e, f, g) -> [Expr] Source #

conjureEquality :: (a, b, c, d, e, f, g) -> Maybe Expr Source #

conjureTiers :: (a, b, c, d, e, f, g) -> Maybe [[Expr]] Source #

conjureSubTypes :: (a, b, c, d, e, f, g) -> Reification Source #

conjureIf :: (a, b, c, d, e, f, g) -> Expr Source #

conjureCases :: (a, b, c, d, e, f, g) -> [Expr] Source #

conjureArgumentCases :: (a, b, c, d, e, f, g) -> [[Expr]] Source #

conjureSize :: (a, b, c, d, e, f, g) -> Int Source #

conjureExpress :: (a, b, c, d, e, f, g) -> Expr -> Expr Source #

conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a, b, c, d, e, f, g) Source #

conjureType :: Conjurable a => a -> Reification Source #

To be used in the implementation of conjureSubTypes.

instance ... => Conjurable <Type> where
  ...
  conjureSubTypes x  =  conjureType (field1 x)
                     .  conjureType (field2 x)
                     .  ...
                     .  conjureType (fieldN x)
  ...

reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]] Source #

Reifies equality to be used in a conjurable type.

This is to be used in the definition of conjureTiers of Conjurable typeclass instances:

instance ... => Conjurable <Type> where
  ...
  conjureTiers  =  reifyTiers
  ...

reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr Source #

Reifies equality == in a Conjurable type instance.

This is to be used in the definition of conjureEquality of Conjurable typeclass instances:

instance ... => Conjurable <Type> where
  ...
  conjureEquality  =  reifyEquality
  ...

reifyExpress :: (Express a, Show a) => a -> Expr -> Expr Source #

Reifies the expr function in a Conjurable type instance.

This is to be used in the definition of conjureExpress of Conjurable typeclass instances.

instance ... => Conjurable <Type> where
  ...
  conjureExpress  =  reifyExpress
  ...

conjureApplication :: Conjurable f => String -> f -> Expr Source #

Computes a complete application for the given function.

> conjureApplication "not" not
not p :: Bool
> conjureApplication "+" ((+) :: Int -> Int -> Int)
x + y :: Int

(cf. conjureVarApplication)

conjureVarApplication :: Conjurable f => String -> f -> Expr Source #

Computes a complete application for a variable of the same type of the given function.

> conjureVarApplication "not" not
not p :: Bool
> conjureVarApplication "+" ((+) :: Int -> Int -> Int)
x + y :: Int

(cf. conjureApplication)

conjurePats :: Conjurable f => [Expr] -> String -> f -> [[[Expr]]] Source #

Computes tiers of sets of patterns for the given function.

> conjurePats [zero] "f" (undefined :: Int -> Int)
[[[f x :: Int]],[[f 0 :: Int,f x :: Int]]]

conjureHoles :: Conjurable f => f -> [Expr] Source #

Computes a list of holes encoded as Exprs from a Conjurable functional value.

(cf. cjHoles)

conjureTiersFor :: Conjurable f => f -> Expr -> [[Expr]] Source #

Compute tiers of values encoded as Exprs of the type of the given Expr.

conjureAreEqual :: Conjurable f => f -> Int -> Expr -> Expr -> Bool Source #

Given a Conjurable functional value, computes a function that checks whether two Exprs are equal up to a given number of tests.

conjureMkEquation :: Conjurable f => f -> Expr -> Expr -> Expr Source #

Computes a function that makes an equation between two expressions.

data A #

Generic type A.

Can be used to test polymorphic functions with a type variable such as take or sort:

take :: Int -> [a] -> [a]
sort :: Ord a => [a] -> [a]

by binding them to the following types:

take :: Int -> [A] -> [A]
sort :: [A] -> [A]

This type is homomorphic to Nat6, B, C, D, E and F.

It is instance to several typeclasses so that it can be used to test functions with type contexts.

Instances

Instances details
Bounded A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: A #

maxBound :: A #

Enum A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: A -> A #

pred :: A -> A #

toEnum :: Int -> A #

fromEnum :: A -> Int #

enumFrom :: A -> [A] #

enumFromThen :: A -> A -> [A] #

enumFromTo :: A -> A -> [A] #

enumFromThenTo :: A -> A -> A -> [A] #

Eq A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: A -> A -> Bool #

(/=) :: A -> A -> Bool #

Integral A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: A -> A -> A #

rem :: A -> A -> A #

div :: A -> A -> A #

mod :: A -> A -> A #

quotRem :: A -> A -> (A, A) #

divMod :: A -> A -> (A, A) #

toInteger :: A -> Integer #

Num A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: A -> A -> A #

(-) :: A -> A -> A #

(*) :: A -> A -> A #

negate :: A -> A #

abs :: A -> A #

signum :: A -> A #

fromInteger :: Integer -> A #

Ord A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: A -> A -> Ordering #

(<) :: A -> A -> Bool #

(<=) :: A -> A -> Bool #

(>) :: A -> A -> Bool #

(>=) :: A -> A -> Bool #

max :: A -> A -> A #

min :: A -> A -> A #

Read A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: A -> Rational #

Show A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> A -> ShowS #

show :: A -> String #

showList :: [A] -> ShowS #

Ix A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (A, A) -> [A] #

index :: (A, A) -> A -> Int #

unsafeIndex :: (A, A) -> A -> Int #

inRange :: (A, A) -> A -> Bool #

rangeSize :: (A, A) -> Int #

unsafeRangeSize :: (A, A) -> Int #

Express A Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: A -> Expr #

Name A Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: A -> String #

Listable A 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[A]] #

list :: [A] #

Conjurable A Source # 
Instance details

Defined in Conjure.Conjurable

data B #

Generic type B.

Can be used to test polymorphic functions with two type variables such as map or foldr:

map :: (a -> b) -> [a] -> [b]
foldr :: (a -> b -> b) -> b -> [a] -> b

by binding them to the following types:

map :: (A -> B) -> [A] -> [B]
foldr :: (A -> B -> B) -> B -> [A] -> B

This type is homomorphic to A, Nat6, C, D, E and F.

Instances

Instances details
Bounded B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: B #

maxBound :: B #

Enum B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: B -> B #

pred :: B -> B #

toEnum :: Int -> B #

fromEnum :: B -> Int #

enumFrom :: B -> [B] #

enumFromThen :: B -> B -> [B] #

enumFromTo :: B -> B -> [B] #

enumFromThenTo :: B -> B -> B -> [B] #

Eq B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: B -> B -> Bool #

(/=) :: B -> B -> Bool #

Integral B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: B -> B -> B #

rem :: B -> B -> B #

div :: B -> B -> B #

mod :: B -> B -> B #

quotRem :: B -> B -> (B, B) #

divMod :: B -> B -> (B, B) #

toInteger :: B -> Integer #

Num B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: B -> B -> B #

(-) :: B -> B -> B #

(*) :: B -> B -> B #

negate :: B -> B #

abs :: B -> B #

signum :: B -> B #

fromInteger :: Integer -> B #

Ord B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: B -> B -> Ordering #

(<) :: B -> B -> Bool #

(<=) :: B -> B -> Bool #

(>) :: B -> B -> Bool #

(>=) :: B -> B -> Bool #

max :: B -> B -> B #

min :: B -> B -> B #

Read B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: B -> Rational #

Show B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> B -> ShowS #

show :: B -> String #

showList :: [B] -> ShowS #

Ix B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (B, B) -> [B] #

index :: (B, B) -> B -> Int #

unsafeIndex :: (B, B) -> B -> Int #

inRange :: (B, B) -> B -> Bool #

rangeSize :: (B, B) -> Int #

unsafeRangeSize :: (B, B) -> Int #

Express B Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: B -> Expr #

Name B Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: B -> String #

Listable B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[B]] #

list :: [B] #

Conjurable B Source # 
Instance details

Defined in Conjure.Conjurable

data C #

Generic type C.

Can be used to test polymorphic functions with three type variables such as uncurry or zipWith:

uncurry :: (a -> b -> c) -> (a, b) -> c
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]

by binding them to the following types:

uncurry :: (A -> B -> C) -> (A, B) -> C
zipWith :: (A -> B -> C) -> [A] -> [B] -> [C]

This type is homomorphic to A, B, Nat6, D, E and F.

Instances

Instances details
Bounded C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: C #

maxBound :: C #

Enum C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: C -> C #

pred :: C -> C #

toEnum :: Int -> C #

fromEnum :: C -> Int #

enumFrom :: C -> [C] #

enumFromThen :: C -> C -> [C] #

enumFromTo :: C -> C -> [C] #

enumFromThenTo :: C -> C -> C -> [C] #

Eq C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: C -> C -> Bool #

(/=) :: C -> C -> Bool #

Integral C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: C -> C -> C #

rem :: C -> C -> C #

div :: C -> C -> C #

mod :: C -> C -> C #

quotRem :: C -> C -> (C, C) #

divMod :: C -> C -> (C, C) #

toInteger :: C -> Integer #

Num C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: C -> C -> C #

(-) :: C -> C -> C #

(*) :: C -> C -> C #

negate :: C -> C #

abs :: C -> C #

signum :: C -> C #

fromInteger :: Integer -> C #

Ord C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: C -> C -> Ordering #

(<) :: C -> C -> Bool #

(<=) :: C -> C -> Bool #

(>) :: C -> C -> Bool #

(>=) :: C -> C -> Bool #

max :: C -> C -> C #

min :: C -> C -> C #

Read C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: C -> Rational #

Show C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> C -> ShowS #

show :: C -> String #

showList :: [C] -> ShowS #

Ix C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (C, C) -> [C] #

index :: (C, C) -> C -> Int #

unsafeIndex :: (C, C) -> C -> Int #

inRange :: (C, C) -> C -> Bool #

rangeSize :: (C, C) -> Int #

unsafeRangeSize :: (C, C) -> Int #

Express C Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: C -> Expr #

Name C Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: C -> String #

Listable C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[C]] #

list :: [C] #

Conjurable C Source # 
Instance details

Defined in Conjure.Conjurable

data D #

Generic type D.

Can be used to test polymorphic functions with four type variables.

This type is homomorphic to A, B, C, Nat6, E and F.

Instances

Instances details
Bounded D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: D #

maxBound :: D #

Enum D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: D -> D #

pred :: D -> D #

toEnum :: Int -> D #

fromEnum :: D -> Int #

enumFrom :: D -> [D] #

enumFromThen :: D -> D -> [D] #

enumFromTo :: D -> D -> [D] #

enumFromThenTo :: D -> D -> D -> [D] #

Eq D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: D -> D -> Bool #

(/=) :: D -> D -> Bool #

Integral D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: D -> D -> D #

rem :: D -> D -> D #

div :: D -> D -> D #

mod :: D -> D -> D #

quotRem :: D -> D -> (D, D) #

divMod :: D -> D -> (D, D) #

toInteger :: D -> Integer #

Num D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: D -> D -> D #

(-) :: D -> D -> D #

(*) :: D -> D -> D #

negate :: D -> D #

abs :: D -> D #

signum :: D -> D #

fromInteger :: Integer -> D #

Ord D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: D -> D -> Ordering #

(<) :: D -> D -> Bool #

(<=) :: D -> D -> Bool #

(>) :: D -> D -> Bool #

(>=) :: D -> D -> Bool #

max :: D -> D -> D #

min :: D -> D -> D #

Read D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: D -> Rational #

Show D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> D -> ShowS #

show :: D -> String #

showList :: [D] -> ShowS #

Ix D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (D, D) -> [D] #

index :: (D, D) -> D -> Int #

unsafeIndex :: (D, D) -> D -> Int #

inRange :: (D, D) -> D -> Bool #

rangeSize :: (D, D) -> Int #

unsafeRangeSize :: (D, D) -> Int #

Express D Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: D -> Expr #

Name D Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: D -> String #

Listable D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[D]] #

list :: [D] #

Conjurable D Source # 
Instance details

Defined in Conjure.Conjurable

data E #

Generic type E.

Can be used to test polymorphic functions with five type variables.

This type is homomorphic to A, B, C, D, Nat6 and F.

Instances

Instances details
Bounded E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: E #

maxBound :: E #

Enum E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: E -> E #

pred :: E -> E #

toEnum :: Int -> E #

fromEnum :: E -> Int #

enumFrom :: E -> [E] #

enumFromThen :: E -> E -> [E] #

enumFromTo :: E -> E -> [E] #

enumFromThenTo :: E -> E -> E -> [E] #

Eq E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: E -> E -> Bool #

(/=) :: E -> E -> Bool #

Integral E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: E -> E -> E #

rem :: E -> E -> E #

div :: E -> E -> E #

mod :: E -> E -> E #

quotRem :: E -> E -> (E, E) #

divMod :: E -> E -> (E, E) #

toInteger :: E -> Integer #

Num E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: E -> E -> E #

(-) :: E -> E -> E #

(*) :: E -> E -> E #

negate :: E -> E #

abs :: E -> E #

signum :: E -> E #

fromInteger :: Integer -> E #

Ord E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: E -> E -> Ordering #

(<) :: E -> E -> Bool #

(<=) :: E -> E -> Bool #

(>) :: E -> E -> Bool #

(>=) :: E -> E -> Bool #

max :: E -> E -> E #

min :: E -> E -> E #

Read E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: E -> Rational #

Show E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> E -> ShowS #

show :: E -> String #

showList :: [E] -> ShowS #

Ix E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (E, E) -> [E] #

index :: (E, E) -> E -> Int #

unsafeIndex :: (E, E) -> E -> Int #

inRange :: (E, E) -> E -> Bool #

rangeSize :: (E, E) -> Int #

unsafeRangeSize :: (E, E) -> Int #

Express E Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: E -> Expr #

Name E Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: E -> String #

Listable E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[E]] #

list :: [E] #

Conjurable E Source # 
Instance details

Defined in Conjure.Conjurable

data F #

Generic type F.

Can be used to test polymorphic functions with five type variables.

This type is homomorphic to A, B, C, D, E and Nat6.

Instances

Instances details
Bounded F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

minBound :: F #

maxBound :: F #

Enum F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

succ :: F -> F #

pred :: F -> F #

toEnum :: Int -> F #

fromEnum :: F -> Int #

enumFrom :: F -> [F] #

enumFromThen :: F -> F -> [F] #

enumFromTo :: F -> F -> [F] #

enumFromThenTo :: F -> F -> F -> [F] #

Eq F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(==) :: F -> F -> Bool #

(/=) :: F -> F -> Bool #

Integral F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

quot :: F -> F -> F #

rem :: F -> F -> F #

div :: F -> F -> F #

mod :: F -> F -> F #

quotRem :: F -> F -> (F, F) #

divMod :: F -> F -> (F, F) #

toInteger :: F -> Integer #

Num F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

(+) :: F -> F -> F #

(-) :: F -> F -> F #

(*) :: F -> F -> F #

negate :: F -> F #

abs :: F -> F #

signum :: F -> F #

fromInteger :: Integer -> F #

Ord F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

compare :: F -> F -> Ordering #

(<) :: F -> F -> Bool #

(<=) :: F -> F -> Bool #

(>) :: F -> F -> Bool #

(>=) :: F -> F -> Bool #

max :: F -> F -> F #

min :: F -> F -> F #

Read F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Real F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

toRational :: F -> Rational #

Show F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

showsPrec :: Int -> F -> ShowS #

show :: F -> String #

showList :: [F] -> ShowS #

Ix F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

range :: (F, F) -> [F] #

index :: (F, F) -> F -> Int #

unsafeIndex :: (F, F) -> F -> Int #

inRange :: (F, F) -> F -> Bool #

rangeSize :: (F, F) -> Int #

unsafeRangeSize :: (F, F) -> Int #

Express F Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: F -> Expr #

Name F Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: F -> String #

Listable F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[F]] #

list :: [F] #

Conjurable F Source # 
Instance details

Defined in Conjure.Conjurable

conjureIsDeconstructor :: Conjurable f => f -> Int -> Expr -> Bool Source #

Checks if an unary function encoded as an Expr is a deconstructor.

(cf. conjureIsDeconstruction)

conjureIsDeconstruction :: Conjurable f => f -> Int -> Expr -> Bool Source #

Checks if an expression is a deconstruction.

There should be a single hole in the expression.

  1. The result does not increase the size for at least half the time.
  2. The result decreases in size for at least a third of the time.

(cf. conjureIsDeconstructor)

candidateDeconstructionsFrom :: Expr -> [Expr] Source #

Compute candidate deconstructions from an Expr.

This is used in the implementation of candidateDefnsC and candidateExprs followed by conjureIsDeconstruction.

conjureIsUnbreakable :: Conjurable f => f -> Expr -> Bool Source #

Checks if an Expr is of an unbreakable type.

conjureReification :: Conjurable a => a -> [Reification1] Source #

Conjures a list of Reification1 for a Conjurable type, its subtypes and Bool.

This is used in the implementation of conjureHoles, conjureMkEquation, conjureAreEqual, conjureTiersFor, conjureIsDeconstructor, conjureNamesFor, conjureIsUnbreakable, etc.

conjureReification1 :: Conjurable a => a -> Reification1 Source #

Conjures a Reification1 for a Conjurable type.

This is used in the implementation of conjureReification.

cevaluate :: Conjurable f => Int -> Defn -> Maybe f Source #

Evaluates a Defn into a regular Haskell value returning Nothing when there's a type mismatch.

The integer argument indicates the limit of recursive evaluations.

ceval :: Conjurable f => Int -> f -> Defn -> f Source #

Evaluates a Defn into a regular Haskell value returning the given default value when there's a type mismatch.

The integer argument indicates the limit of recursive evaluations.

cevl :: Conjurable f => Int -> Defn -> f Source #

Evaluates a Defn into a regular Haskell value raising an error there's a type mismatch.

The integer argument indicates the limit of recursive evaluations.

class Name a where #

If we were to come up with a variable name for the given type what name would it be?

An instance for a given type Ty is simply given by:

instance Name Ty where name _ = "x"

Examples:

> name (undefined :: Int)
"x"
> name (undefined :: Bool)
"p"
> name (undefined :: [Int])
"xs"

This is then used to generate an infinite list of variable names:

> names (undefined :: Int)
["x", "y", "z", "x'", "y'", "z'", "x''", "y''", "z''", ...]
> names (undefined :: Bool)
["p", "q", "r", "p'", "q'", "r'", "p''", "q''", "r''", ...]
> names (undefined :: [Int])
["xs", "ys", "zs", "xs'", "ys'", "zs'", "xs''", "ys''", ...]

Minimal complete definition

Nothing

Methods

name :: a -> String #

O(1).

Returns a name for a variable of the given argument's type.

> name (undefined :: Int)
"x"
> name (undefined :: [Bool])
"ps"
> name (undefined :: [Maybe Integer])
"mxs"

The default definition is:

name _ = "x"

Instances

Instances details
Name Bool
name (undefined :: Bool) = "p"
names (undefined :: Bool) = ["p", "q", "r", "p'", "q'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Bool -> String #

Name Char
name (undefined :: Char) = "c"
names (undefined :: Char) = ["c", "d", "e", "c'", "d'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Char -> String #

Name Double
name (undefined :: Double) = "x"
names (undefined :: Double) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Double -> String #

Name Float
name (undefined :: Float) = "x"
names (undefined :: Float) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Float -> String #

Name Int
name (undefined :: Int) = "x"
names (undefined :: Int) = ["x", "y", "z", "x'", "y'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Int -> String #

Name Int8 
Instance details

Defined in Data.Express.Name

Methods

name :: Int8 -> String #

Name Int16 
Instance details

Defined in Data.Express.Name

Methods

name :: Int16 -> String #

Name Int32 
Instance details

Defined in Data.Express.Name

Methods

name :: Int32 -> String #

Name Int64 
Instance details

Defined in Data.Express.Name

Methods

name :: Int64 -> String #

Name Integer
name (undefined :: Integer) = "x"
names (undefined :: Integer) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Integer -> String #

Name Ordering
name (undefined :: Ordering) = "o"
names (undefined :: Ordering) = ["o", "p", "q", "o'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Ordering -> String #

Name Word 
Instance details

Defined in Data.Express.Name

Methods

name :: Word -> String #

Name Word8 
Instance details

Defined in Data.Express.Name

Methods

name :: Word8 -> String #

Name Word16 
Instance details

Defined in Data.Express.Name

Methods

name :: Word16 -> String #

Name Word32 
Instance details

Defined in Data.Express.Name

Methods

name :: Word32 -> String #

Name Word64 
Instance details

Defined in Data.Express.Name

Methods

name :: Word64 -> String #

Name ()
name (undefined :: ()) = "u"
names (undefined :: ()) = ["u", "v", "w", "u'", "v'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: () -> String #

Name GeneralCategory 
Instance details

Defined in Data.Express.Name

Name A Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: A -> String #

Name B Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: B -> String #

Name C Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: C -> String #

Name D Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: D -> String #

Name E Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: E -> String #

Name F Source # 
Instance details

Defined in Conjure.Conjurable

Methods

name :: F -> String #

Name a => Name [a]
names (undefined :: [Int]) = ["xs", "ys", "zs", "xs'", ...]
names (undefined :: [Bool]) = ["ps", "qs", "rs", "ps'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: [a] -> String #

Name a => Name (Maybe a)
names (undefined :: Maybe Int) = ["mx", "mx1", "mx2", ...]
nemes (undefined :: Maybe Bool) = ["mp", "mp1", "mp2", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Maybe a -> String #

Name (Ratio a)
name (undefined :: Rational) = "q"
names (undefined :: Rational) = ["q", "r", "s", "q'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Ratio a -> String #

Name (Complex a)
name (undefined :: Complex) = "x"
names (undefined :: Complex) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Complex a -> String #

Name (a -> b)
names (undefined :: ()->()) = ["f", "g", "h", "f'", ...]
names (undefined :: Int->Int) = ["f", "g", "h", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a -> b) -> String #

(Name a, Name b) => Name (Either a b)
names (undefined :: Either Int Int) = ["exy", "exy1", ...]
names (undefined :: Either Int Bool) = ["exp", "exp1", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Either a b -> String #

(Name a, Name b) => Name (a, b)
names (undefined :: (Int,Int)) = ["xy", "zw", "xy'", ...]
names (undefined :: (Bool,Bool)) = ["pq", "rs", "pq'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b) -> String #

(Name a, Name b, Name c) => Name (a, b, c)
names (undefined :: (Int,Int,Int)) = ["xyz","uvw", ...]
names (undefined :: (Int,Bool,Char)) = ["xpc", "xpc1", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c) -> String #

(Name a, Name b, Name c, Name d) => Name (a, b, c, d)
names (undefined :: ((),(),(),())) = ["uuuu", "uuuu1", ...]
names (undefined :: (Int,Int,Int,Int)) = ["xxxx", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d) -> String #

(Name a, Name b, Name c, Name d, Name e) => Name (a, b, c, d, e) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f) => Name (a, b, c, d, e, f) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g) => Name (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h) => Name (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i) => Name (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j) => Name (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k) => Name (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j, k) -> String #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k, Name l) => Name (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String #

class (Show a, Typeable a) => Express a where #

Express typeclass instances provide an expr function that allows values to be deeply encoded as applications of Exprs.

expr False  =  val False
expr (Just True)  =  value "Just" (Just :: Bool -> Maybe Bool) :$ val True

The function expr can be contrasted with the function val:

  • val always encodes values as atomic Value Exprs -- shallow encoding.
  • expr ideally encodes expressions as applications (:$) between Value Exprs -- deep encoding.

Depending on the situation, one or the other may be desirable.

Instances can be automatically derived using the TH function deriveExpress.

The following example shows a datatype and its instance:

data Stack a = Stack a (Stack a) | Empty
instance Express a => Express (Stack a) where
  expr s@(Stack x y) = value "Stack" (Stack ->>: s) :$ expr x :$ expr y
  expr s@Empty       = value "Empty" (Empty   -: s)

To declare expr it may be useful to use auxiliary type binding operators: -:, ->:, ->>:, ->>>:, ->>>>:, ->>>>>:, ...

For types with atomic values, just declare expr = val

Methods

expr :: a -> Expr #

Instances

Instances details
Express Bool 
Instance details

Defined in Data.Express.Express

Methods

expr :: Bool -> Expr #

Express Char 
Instance details

Defined in Data.Express.Express

Methods

expr :: Char -> Expr #

Express Double 
Instance details

Defined in Data.Express.Express

Methods

expr :: Double -> Expr #

Express Float 
Instance details

Defined in Data.Express.Express

Methods

expr :: Float -> Expr #

Express Int 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int -> Expr #

Express Int8 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int8 -> Expr #

Express Int16 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int16 -> Expr #

Express Int32 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int32 -> Expr #

Express Int64 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int64 -> Expr #

Express Integer 
Instance details

Defined in Data.Express.Express

Methods

expr :: Integer -> Expr #

Express Ordering 
Instance details

Defined in Data.Express.Express

Methods

expr :: Ordering -> Expr #

Express Word 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word -> Expr #

Express Word8 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word8 -> Expr #

Express Word16 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word16 -> Expr #

Express Word32 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word32 -> Expr #

Express Word64 
Instance details

Defined in Data.Express.Express

Methods

expr :: Word64 -> Expr #

Express () 
Instance details

Defined in Data.Express.Express

Methods

expr :: () -> Expr #

Express GeneralCategory 
Instance details

Defined in Data.Express.Express

Methods

expr :: GeneralCategory -> Expr #

Express A Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: A -> Expr #

Express B Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: B -> Expr #

Express C Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: C -> Expr #

Express D Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: D -> Expr #

Express E Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: E -> Expr #

Express F Source # 
Instance details

Defined in Conjure.Expr

Methods

expr :: F -> Expr #

Express a => Express [a] 
Instance details

Defined in Data.Express.Express

Methods

expr :: [a] -> Expr #

Express a => Express (Maybe a) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Maybe a -> Expr #

(Integral a, Express a) => Express (Ratio a) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Ratio a -> Expr #

(RealFloat a, Express a) => Express (Complex a) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Complex a -> Expr #

(Express a, Express b) => Express (Either a b) 
Instance details

Defined in Data.Express.Express

Methods

expr :: Either a b -> Expr #

(Express a, Express b) => Express (a, b) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b) -> Expr #

(Express a, Express b, Express c) => Express (a, b, c) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c) -> Expr #

(Express a, Express b, Express c, Express d) => Express (a, b, c, d) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d) -> Expr #

(Express a, Express b, Express c, Express d, Express e) => Express (a, b, c, d, e) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f) => Express (a, b, c, d, e, f) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g) => Express (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h) => Express (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i) => Express (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j) => Express (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j, Express k) => Express (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j, k) -> Expr #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j, Express k, Express l) => Express (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr #

Orphan instances

Name A Source # 
Instance details

Methods

name :: A -> String #

Name B Source # 
Instance details

Methods

name :: B -> String #

Name C Source # 
Instance details

Methods

name :: C -> String #

Name D Source # 
Instance details

Methods

name :: D -> String #

Name E Source # 
Instance details

Methods

name :: E -> String #

Name F Source # 
Instance details

Methods

name :: F -> String #