code-conjure-0.4.2: conjure 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.

A hole, an equality function and tiers.

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.

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

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

conjureSubTypes :: a -> Reification Source #

conjureIf :: a -> Expr Source #

conjureCases :: a -> [Expr] Source #

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

conjureSize :: a -> Int Source #

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

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 #

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 to be used in a conjurable type.

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 #

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

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

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

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

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 #