module Conjure.Conjurable
( Reification1
, Reification
, Conjurable (..)
, conjureType
, reifyTiers
, reifyEquality
, reifyExpress
, conjureApplication
, conjureVarApplication
, conjurePats
, conjureHoles
, conjureTiersFor
, conjureAreEqual
, conjureMkEquation
, A, B, C, D, E, F
, conjureIsDeconstruction
, candidateDeconstructionsFrom
, candidateDeconstructionsFromHoled
, conjureIsUnbreakable
, conjureReification
, conjureReification1
, conjureDynamicEq
, conjureIsNumeric
, cevaluate
, ceval
, cevl
, Name (..)
, Express (..)
, conjureArgumentPats
, conjureMostGeneralCanonicalVariation
)
where
import Test.LeanCheck
import Test.LeanCheck.Utils
import Test.LeanCheck.Error (errorToFalse)
import Conjure.Expr hiding (application)
import Conjure.Defn
import Test.Speculate.Expr
import Data.Functor ((<$>))
import Control.Applicative ((<*>))
import Data.Dynamic
import Data.Express
import Data.Int
import Data.Word
import Data.Ratio
import Data.Complex
type Reification1 = (Expr, Maybe Expr, Maybe [[Expr]], [String], Bool, Expr)
type Reification = [Reification1] -> [Reification1]
type Prim = (Expr, Reification)
pr :: (Conjurable a, Show a) => a -> Prim
pr :: forall a. (Conjurable a, Show a) => a -> Prim
pr a
x = (a -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val a
x, a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x)
prim :: Conjurable a => String -> a -> Prim
prim :: forall a. Conjurable a => String -> a -> Prim
prim String
s a
x = (String -> a -> Expr
forall a. Typeable a => String -> a -> Expr
value String
s a
x, a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x)
class (Typeable a, Name a) => Conjurable a where
conjureArgumentHoles :: a -> [Expr]
conjureArgumentHoles a
_ = []
conjureEquality :: a -> Maybe Expr
conjureEquality a
_ = Maybe Expr
forall a. Maybe a
Nothing
conjureTiers :: a -> Maybe [[Expr]]
conjureTiers a
_ = Maybe [[Expr]]
forall a. Maybe a
Nothing
conjureSubTypes :: a -> Reification
conjureSubTypes a
_ = Reification
forall a. a -> a
id
conjureIf :: a -> Expr
conjureIf = a -> Expr
forall a. Typeable a => a -> Expr
ifFor
conjureCases :: a -> [Expr]
conjureCases a
_ = []
conjureArgumentCases :: a -> [[Expr]]
conjureArgumentCases a
_ = []
conjureSize :: a -> Int
conjureSize a
_ = Int
0
conjureExpress :: a -> Expr -> Expr
conjureEvaluate :: (Expr->Expr) -> Int -> Defn -> Expr -> Maybe a
conjureEvaluate = (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a
forall a.
Typeable a =>
(Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a
devaluate
conjureType :: Conjurable a => a -> Reification
conjureType :: forall a. Conjurable a => a -> Reification
conjureType a
x [Reification1]
ms =
if a -> Expr
forall a. Typeable a => a -> Expr
hole a
x Expr -> [Expr] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Expr
h | (Expr
h,Maybe Expr
_,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- [Reification1]
ms]
then [Reification1]
ms
else a -> Reification
forall a. Conjurable a => a -> Reification
conjureSubTypes a
x Reification -> Reification
forall a b. (a -> b) -> a -> b
$ a -> Reification1
forall a. Conjurable a => a -> Reification1
conjureReification1 a
x Reification1 -> Reification
forall a. a -> [a] -> [a]
: [Reification1]
ms
nubConjureType :: Conjurable a => a -> Reification
nubConjureType :: forall a. Conjurable a => a -> Reification
nubConjureType a
x = (Reification1 -> Expr) -> Reification
forall b a. Eq b => (a -> b) -> [a] -> [a]
nubOn (\(Expr
eh,Maybe Expr
_,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) -> Expr
eh) Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
conjureReification1 :: Conjurable a => a -> Reification1
conjureReification1 :: forall a. Conjurable a => a -> Reification1
conjureReification1 a
x = (a -> Expr
forall a. Typeable a => a -> Expr
hole a
x, a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x, a -> Maybe [[Expr]]
forall a. Conjurable a => a -> Maybe [[Expr]]
conjureTiers a
x, a -> [String]
forall a. Name a => a -> [String]
names a
x, [Expr] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Expr] -> Bool) -> [Expr] -> Bool
forall a b. (a -> b) -> a -> b
$ a -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureCases a
x, String -> (a -> Int) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"conjureSize" (a -> Int
forall a. Conjurable a => a -> Int
conjureSize (a -> Int) -> a -> a -> Int
forall a b. (a -> b) -> a -> a -> b
-:> a
x))
conjureReification :: Conjurable a => a -> [Reification1]
conjureReification :: forall a. Conjurable a => a -> [Reification1]
conjureReification a
x = a -> Reification
forall a. Conjurable a => a -> Reification
nubConjureType a
x [Bool -> Reification1
forall a. Conjurable a => a -> Reification1
conjureReification1 Bool
bool]
where
bool :: Bool
bool :: Bool
bool = String -> Bool
forall a. HasCallStack => String -> a
error String
"conjureReification: evaluated proxy boolean value (definitely a bug)"
reifyEquality :: (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality :: forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality = Expr -> Maybe Expr
forall a. a -> Maybe a
Just (Expr -> Maybe Expr) -> (a -> Expr) -> a -> Maybe Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Expr] -> Expr
forall a. HasCallStack => [a] -> a
head ([Expr] -> Expr) -> (a -> [Expr]) -> a -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Expr]
forall a. (Typeable a, Eq a) => a -> [Expr]
reifyEq
reifyTiers :: (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers :: forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers = [[Expr]] -> Maybe [[Expr]]
forall a. a -> Maybe a
Just ([[Expr]] -> Maybe [[Expr]])
-> (a -> [[Expr]]) -> a -> Maybe [[Expr]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> [[Expr]]
mkExprTiers
reifyExpress :: (Express a, Show a) => a -> Expr -> Expr
reifyExpress :: forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress a
a Expr
e = case Expr
exprE Expr -> Expr -> Maybe Expr
$$ Expr
e of
Maybe Expr
Nothing -> Expr
e
Just Expr
e' -> Expr -> Expr -> Expr
forall a. Typeable a => a -> Expr -> a
eval (String -> Expr
forall a. HasCallStack => String -> a
error (String -> Expr) -> String -> Expr
forall a b. (a -> b) -> a -> b
$ String
"reifyExpress: cannot eval " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
forall a. Show a => a -> String
show Expr
e') Expr
e'
where
exprE :: Expr
exprE = String -> (a -> Expr) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"expr" (a -> Expr
forall a. Express a => a -> Expr
expr (a -> Expr) -> a -> a -> Expr
forall a b. (a -> b) -> a -> a -> b
-:> a
a)
mkExprTiers :: (Listable a, Show a, Typeable a) => a -> [[Expr]]
mkExprTiers :: forall a. (Listable a, Show a, Typeable a) => a -> [[Expr]]
mkExprTiers a
a = (a -> Expr) -> [[a]] -> [[Expr]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT a -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val ([[a]]
forall a. Listable a => [[a]]
tiers [[a]] -> [[a]] -> [[a]]
forall a. a -> a -> a
-: [[a
a]])
conjureHoles :: Conjurable f => f -> [Expr]
conjureHoles :: forall a. Conjurable a => a -> [Expr]
conjureHoles f
f = [Expr
eh | (Expr
eh,Maybe Expr
_,Just [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- f -> [Reification1]
forall a. Conjurable a => a -> [Reification1]
conjureReification f
f]
conjureMkEquation :: Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation :: forall f. Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation f
f = [Expr] -> Expr -> Expr -> Expr
mkEquation [Expr
eq | (Expr
_,Just Expr
eq,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- f -> [Reification1]
forall a. Conjurable a => a -> [Reification1]
conjureReification f
f]
conjureDynamicEq :: Conjurable f => f -> Dynamic
conjureDynamicEq :: forall f. Conjurable f => f -> Dynamic
conjureDynamicEq f
f = case f -> Expr -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation f
f Expr
efxs Expr
efxs of
(Value String
"==" Dynamic
deq :$ Expr
_ :$ Expr
_) -> Dynamic
deq
Expr
_ -> String -> Dynamic
forall a. HasCallStack => String -> a
error String
"conjureDynamicEq: expected an == but found something else. Bug!"
where
efxs :: Expr
efxs = String -> f -> Expr
forall f. Conjurable f => String -> f -> Expr
conjureApplication String
"f" f
f
conjureAreEqual :: Conjurable f => f -> Int -> Expr -> Expr -> Bool
conjureAreEqual :: forall f. Conjurable f => f -> Int -> Expr -> Expr -> Bool
conjureAreEqual f
f Int
maxTests = Expr -> Expr -> Bool
(===)
where
-==- :: Expr -> Expr -> Expr
(-==-) = f -> Expr -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation f
f
Expr
e1 === :: Expr -> Expr -> Bool
=== Expr
e2 = Expr -> Bool
isTrue (Expr -> Bool) -> Expr -> Bool
forall a b. (a -> b) -> a -> b
$ Expr
e1 Expr -> Expr -> Expr
-==- Expr
e2
isTrue :: Expr -> Bool
isTrue = (Expr -> Bool) -> [Expr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
errorToFalse (Bool -> Bool) -> (Expr -> Bool) -> Expr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Expr -> Bool
forall a. Typeable a => a -> Expr -> a
eval Bool
False) ([Expr] -> Bool) -> (Expr -> [Expr]) -> Expr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
gs
gs :: Expr -> [Expr]
gs = Int -> [Expr] -> [Expr]
forall a. Int -> [a] -> [a]
take Int
maxTests ([Expr] -> [Expr]) -> (Expr -> [Expr]) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> [[Expr]]) -> Expr -> [Expr]
grounds (f -> Expr -> [[Expr]]
forall f. Conjurable f => f -> Expr -> [[Expr]]
conjureTiersFor f
f)
conjureTiersFor :: Conjurable f => f -> Expr -> [[Expr]]
conjureTiersFor :: forall f. Conjurable f => f -> Expr -> [[Expr]]
conjureTiersFor f
f Expr
e = [[[Expr]]] -> [[Expr]]
tf [[[Expr]]]
allTiers
where
allTiers :: [ [[Expr]] ]
allTiers :: [[[Expr]]]
allTiers = [[[Expr]]
etiers | (Expr
_,Maybe Expr
_,Just [[Expr]]
etiers,[String]
_,Bool
_,Expr
_) <- f -> [Reification1]
forall a. Conjurable a => a -> [Reification1]
conjureReification f
f]
tf :: [[[Expr]]] -> [[Expr]]
tf [] = [[Expr
e]]
tf ([[Expr]]
etiers:[[[Expr]]]
etc) = case [[Expr]]
etiers of
((Expr
e':[Expr]
_):[[Expr]]
_) | Expr -> TypeRep
typ Expr
e' TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
e -> [[Expr]]
etiers
[[Expr]]
_ -> [[[Expr]]] -> [[Expr]]
tf [[[Expr]]]
etc
conjureIsNumeric :: Conjurable f => f -> Expr -> Bool
conjureIsNumeric :: forall f. Conjurable f => f -> Expr -> Bool
conjureIsNumeric f
f Expr
e = case [[Expr]] -> [Expr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Expr]] -> [Expr]) -> [[Expr]] -> [Expr]
forall a b. (a -> b) -> a -> b
$ f -> Expr -> [[Expr]]
forall f. Conjurable f => f -> Expr -> [[Expr]]
conjureTiersFor f
f Expr
e of
(Value String
"0" Dynamic
_):[Expr]
_ -> Bool
True
[Expr]
_ -> Bool
False
conjureNamesFor :: Conjurable f => f -> Expr -> [String]
conjureNamesFor :: forall f. Conjurable f => f -> Expr -> [String]
conjureNamesFor f
f Expr
e = [[String]] -> [String]
forall a. HasCallStack => [a] -> a
head
([[String]] -> [String]) -> [[String]] -> [String]
forall a b. (a -> b) -> a -> b
$ [[String]
ns | (Expr
eh, Maybe Expr
_, Maybe [[Expr]]
_, [String]
ns, Bool
_, Expr
_) <- f -> [Reification1]
forall a. Conjurable a => a -> [Reification1]
conjureReification f
f, Expr -> TypeRep
typ Expr
e TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
eh]
[[String]] -> [[String]] -> [[String]]
forall a. [a] -> [a] -> [a]
++ [Int -> [String]
forall a. Name a => a -> [String]
names (Int
forall a. HasCallStack => a
undefined :: Int)]
conjureMostGeneralCanonicalVariation :: Conjurable f => f -> Expr -> Expr
conjureMostGeneralCanonicalVariation :: forall f. Conjurable f => f -> Expr -> Expr
conjureMostGeneralCanonicalVariation f
f = (Expr -> [String]) -> Expr -> Expr
canonicalizeWith (f -> Expr -> [String]
forall f. Conjurable f => f -> Expr -> [String]
conjureNamesFor f
f)
(Expr -> Expr) -> (Expr -> Expr) -> Expr -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Expr
fastMostGeneralVariation
conjureIsDeconstruction :: Conjurable f => f -> Int -> Expr -> Bool
conjureIsDeconstruction :: forall f. Conjurable f => f -> Int -> Expr -> Bool
conjureIsDeconstruction f
f Int
maxTests Expr
ed = [Expr] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Expr -> [Expr]
holes Expr
ed) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
Bool -> Bool -> Bool
&& Expr -> TypeRep
typ Expr
h TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
ed
Bool -> Bool -> Bool
&& (Expr -> Bool) -> [Expr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Expr -> Bool
is [Expr]
gs
where
gs :: [Expr]
gs = Int -> [Expr] -> [Expr]
forall a. Int -> [a] -> [a]
take Int
maxTests ([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ (Expr -> [[Expr]]) -> Expr -> [Expr]
grounds (f -> Expr -> [[Expr]]
forall f. Conjurable f => f -> Expr -> [[Expr]]
conjureTiersFor f
f) Expr
ed
[Expr
h] = Expr -> [Expr]
holes Expr
ed
sz :: Expr
sz = [Expr] -> Expr
forall a. HasCallStack => [a] -> a
head [Expr
sz | (Expr
_, Maybe Expr
_, Maybe [[Expr]]
_, [String]
_, Bool
_, Expr
sz) <- f -> [Reification1]
forall a. Conjurable a => a -> [Reification1]
conjureReification f
f
, Expr -> Bool
isWellTyped (Expr
sz Expr -> Expr -> Expr
:$ Expr
h)]
esz :: Expr -> Int
esz Expr
e = Int -> Expr -> Int
forall a. Typeable a => a -> Expr -> a
eval (Int
0::Int) (Expr
sz Expr -> Expr -> Expr
:$ Expr
e)
a
x << :: a -> a -> Bool
<< a
0 = Bool
True
a
x << a
y = a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
y
is :: Expr -> Bool
is Expr
e = Bool -> Bool
errorToFalse (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Expr -> Int
esz Expr
e Int -> Int -> Bool
forall {a}. (Num a, Ord a) => a -> a -> Bool
<< Expr -> Int
esz (Expr -> Expr
holeValue Expr
e)
holeValue :: Expr -> Expr
holeValue Expr
e = Expr -> Maybe Expr -> Expr
forall a. a -> Maybe a -> a
fromMaybe Expr
forall {a}. a
err
(Maybe Expr -> Expr)
-> (Maybe Defn -> Maybe Expr) -> Maybe Defn -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Defn -> Maybe Expr
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Expr
h
(Defn -> Maybe Expr)
-> (Maybe Defn -> Defn) -> Maybe Defn -> Maybe Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Defn -> Maybe Defn -> Defn
forall a. a -> Maybe a -> a
fromMaybe Defn
forall {a}. a
err
(Maybe Defn -> Expr) -> Maybe Defn -> Expr
forall a b. (a -> b) -> a -> b
$ Expr
e Expr -> Expr -> Maybe Defn
`match` Expr
ed
err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"conjureIsDeconstructor: the impossible happened"
candidateDeconstructionsFrom :: Expr -> [Expr]
candidateDeconstructionsFrom :: Expr -> [Expr]
candidateDeconstructionsFrom Expr
e =
[ Expr
e'
| Expr
v <- Expr -> [Expr]
vars Expr
e
, Expr -> TypeRep
typ Expr
v TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
e
, let e' :: Expr
e' = Expr
e Expr -> Defn -> Expr
//- [(Expr
v, Expr -> Expr
holeAsTypeOf Expr
v)]
, [Expr] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Expr -> [Expr]
holes Expr
e') Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
]
candidateDeconstructionsFromHoled :: Expr -> [Expr]
candidateDeconstructionsFromHoled :: Expr -> [Expr]
candidateDeconstructionsFromHoled Expr
e = (Expr -> Expr) -> [Expr] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map (Expr -> Defn -> Expr
//- [(Expr
v, Expr
h)])
([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ (Expr -> [Expr]) -> [Expr] -> [Expr]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Expr -> [Expr]
canonicalVariations
([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ Expr -> Expr -> [Expr]
deholings Expr
v Expr
e
where
h :: Expr
h = Expr -> Expr
holeAsTypeOf Expr
e
v :: Expr
v = String
"_#_" String -> Expr -> Expr
`varAsTypeOf` Expr
e
conjureIsUnbreakable :: Conjurable f => f -> Expr -> Bool
conjureIsUnbreakable :: forall f. Conjurable f => f -> Expr -> Bool
conjureIsUnbreakable f
f Expr
e = [Bool] -> Bool
forall a. HasCallStack => [a] -> a
head
[Bool
is | (Expr
h,Maybe Expr
_,Maybe [[Expr]]
_,[String]
_,Bool
is,Expr
_) <- f -> [Reification1]
forall a. Conjurable a => a -> [Reification1]
conjureReification f
f, Expr -> TypeRep
typ Expr
h TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
e]
instance Conjurable () where
conjureExpress :: () -> Expr -> Expr
conjureExpress = () -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: () -> Maybe Expr
conjureEquality = () -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: () -> Maybe [[Expr]]
conjureTiers = () -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureCases :: () -> [Expr]
conjureCases ()
_ = [() -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val ()]
instance Conjurable Bool where
conjureExpress :: Bool -> Expr -> Expr
conjureExpress = Bool -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Bool -> Maybe Expr
conjureEquality = Bool -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Bool -> Maybe [[Expr]]
conjureTiers = Bool -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureCases :: Bool -> [Expr]
conjureCases Bool
_ = [Bool -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Bool
False, Bool -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Bool
True]
instance Conjurable Int where
conjureExpress :: Int -> Expr -> Expr
conjureExpress = Int -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Int -> Maybe Expr
conjureEquality = Int -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Int -> Maybe [[Expr]]
conjureTiers = Int -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Int -> Int
conjureSize = Int -> Int
forall {a}. (Ord a, Num a) => a -> a
size where size :: a -> a
size a
x | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = a
0
| Bool
otherwise = a
x
integralSize :: Integral a => a -> Int
integralSize :: forall a. Integral a => a -> Int
integralSize = a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (a -> Int) -> (a -> a) -> a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a
forall {a}. (Ord a, Num a) => a -> a
size where size :: a -> a
size a
x | a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 = a
0
| Bool
otherwise = a
x
instance Conjurable Integer where
conjureExpress :: Integer -> Expr -> Expr
conjureExpress = Integer -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Integer -> Maybe Expr
conjureEquality = Integer -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Integer -> Maybe [[Expr]]
conjureTiers = Integer -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Integer -> Int
conjureSize = Integer -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Char where
conjureExpress :: Char -> Expr -> Expr
conjureExpress = Char -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Char -> Maybe Expr
conjureEquality = Char -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Char -> Maybe [[Expr]]
conjureTiers = Char -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
(==:) :: (a -> a -> Bool) -> a -> (a -> a -> Bool)
==: :: forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
(==:) = (a -> a -> Bool) -> a -> a -> a -> Bool
forall a b. a -> b -> a
const
instance (Conjurable a, Listable a, Express a, Show a) => Conjurable [a] where
conjureExpress :: [a] -> Expr -> Expr
conjureExpress = [a] -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureSubTypes :: [a] -> Reification
conjureSubTypes [a]
xs = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType ([a] -> a
forall a. HasCallStack => [a] -> a
head [a]
xs)
conjureTiers :: [a] -> Maybe [[Expr]]
conjureTiers = [a] -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: [a] -> Int
conjureSize = [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length
conjureCases :: [a] -> [Expr]
conjureCases [a]
xs = [ [a] -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val ([] [a] -> [a] -> [a]
forall a. a -> a -> a
-: [a]
xs)
, String -> (a -> [a] -> [a]) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
":" ((:) (a -> [a] -> [a]) -> [a] -> a -> [a] -> [a]
forall a b c. (a -> b -> c) -> c -> a -> b -> c
->>: [a]
xs) Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
x Expr -> Expr -> Expr
:$ [a] -> Expr
forall a. Typeable a => a -> Expr
hole [a]
xs
] where x :: a
x = [a] -> a
forall a. HasCallStack => [a] -> a
head [a]
xs
conjureEquality :: [a] -> Maybe Expr
conjureEquality [a]
xs = Expr -> Expr
from (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
where
x :: a
x = [a] -> a
forall a. HasCallStack => [a] -> a
head [a]
xs
from :: Expr -> Expr
from Expr
e = String -> ([a] -> [a] -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" [a] -> [a] -> Bool
(==)
where
.==. :: a -> a -> Bool
(.==.) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
[] == :: [a] -> [a] -> Bool
== [] = Bool
True
(a
x:[a]
xs) == [] = Bool
False
[] == (a
y:[a]
ys) = Bool
False
(a
x:[a]
xs) == (a
y:[a]
ys) = a
x a -> a -> Bool
.==. a
y Bool -> Bool -> Bool
&& [a]
xs [a] -> [a] -> Bool
== [a]
ys
instance ( Conjurable a, Listable a, Show a, Express a
, Conjurable b, Listable b, Show b, Express b
) => Conjurable (a,b) where
conjureExpress :: (a, b) -> Expr -> Expr
conjureExpress = (a, b) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b) -> Maybe [[Expr]]
conjureTiers = (a, b) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b) -> Reification
conjureSubTypes (a, b)
xy = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType ((a, b) -> a
forall a b. (a, b) -> a
fst (a, b)
xy)
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType ((a, b) -> b
forall a b. (a, b) -> b
snd (a, b)
xy)
conjureCases :: (a, b) -> [Expr]
conjureCases (a, b)
xy = [String -> (a -> b -> (a, b)) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"," ((,) (a -> b -> (a, b)) -> (a, b) -> a -> b -> (a, b)
forall a b c. (a -> b -> c) -> c -> a -> b -> c
->>: (a, b)
xy) Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
x Expr -> Expr -> Expr
:$ b -> Expr
forall a. Typeable a => a -> Expr
hole b
y]
where
(a
x,b
y) = (a
forall a. HasCallStack => a
undefined,b
forall a. HasCallStack => a
undefined) (a, b) -> (a, b) -> (a, b)
forall a. a -> a -> a
-: (a, b)
xy
conjureEquality :: (a, b) -> Maybe Expr
conjureEquality (a, b)
xy = Expr -> Expr -> Expr
from (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
where
(a
x,b
y) = (a, b)
xy
from :: Expr -> Expr -> Expr
from Expr
e1 Expr
e2 = String -> ((a, b) -> (a, b) -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b) -> (a, b) -> Bool
(==)
where
==. :: a -> a -> Bool
(==.) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.== :: b -> b -> Bool
(.==) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
(a
x1,b
y1) == :: (a, b) -> (a, b) -> Bool
== (a
x2,b
y2) = a
x1 a -> a -> Bool
==. a
x2 Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.== b
y2
instance ( 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) where
conjureExpress :: (a, b, c) -> Expr -> Expr
conjureExpress = (a, b, c) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c) -> Maybe [[Expr]]
conjureTiers = (a, b, c) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c) -> Reification
conjureSubTypes (a, b, c)
xyz = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
where (a
x,b
y,c
z) = (a, b, c)
xyz
conjureCases :: (a, b, c) -> [Expr]
conjureCases (a, b, c)
xyz = [String -> (a -> b -> c -> (a, b, c)) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
",," ((,,) (a -> b -> c -> (a, b, c)) -> (a, b, c) -> a -> b -> c -> (a, b, c)
forall a b c d. (a -> b -> c -> d) -> d -> a -> b -> c -> d
->>>: (a, b, c)
xyz) Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
x Expr -> Expr -> Expr
:$ b -> Expr
forall a. Typeable a => a -> Expr
hole b
y Expr -> Expr -> Expr
:$ c -> Expr
forall a. Typeable a => a -> Expr
hole c
z]
where
(a
x,b
y,c
z) = (a
forall a. HasCallStack => a
undefined,b
forall a. HasCallStack => a
undefined,c
forall a. HasCallStack => a
undefined) (a, b, c) -> (a, b, c) -> (a, b, c)
forall a. a -> a -> a
-: (a, b, c)
xyz
conjureEquality :: (a, b, c) -> Maybe Expr
conjureEquality (a, b, c)
xyz = Expr -> Expr -> Expr -> Expr
from
(Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
where
(a
x,b
y,c
z) = (a, b, c)
xyz
from :: Expr -> Expr -> Expr -> Expr
from Expr
e1 Expr
e2 Expr
e3 = String -> ((a, b, c) -> (a, b, c) -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c) -> (a, b, c) -> Bool
(==)
where
==.. :: a -> a -> Bool
(==..) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==. :: b -> b -> Bool
(.==.) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..== :: c -> c -> Bool
(..==) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
(a
x1,b
y1,c
z1) == :: (a, b, c) -> (a, b, c) -> Bool
== (a
x2,b
y2,c
z2) = a
x1 a -> a -> Bool
==.. a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==. b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..== c
z2
instance (Conjurable a, Listable a, Show a, Express a) => Conjurable (Maybe a) where
conjureExpress :: Maybe a -> Expr -> Expr
conjureExpress = Maybe a -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: Maybe a -> Maybe [[Expr]]
conjureTiers = Maybe a -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: Maybe a -> Reification
conjureSubTypes Maybe a
mx = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType (Maybe a -> a
forall a. HasCallStack => Maybe a -> a
fromJust Maybe a
mx)
conjureCases :: Maybe a -> [Expr]
conjureCases Maybe a
mx = [ String -> Maybe a -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"Nothing" (Maybe a
forall a. Maybe a
Nothing Maybe a -> Maybe a -> Maybe a
forall a. a -> a -> a
-: Maybe a
mx)
, String -> (a -> Maybe a) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"Just" (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> Maybe a -> a -> Maybe a
forall a b. (a -> b) -> b -> a -> b
->: Maybe a
mx) Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
x
]
where
Just a
x = Maybe a
forall a. HasCallStack => a
undefined Maybe a -> Maybe a -> Maybe a
forall a. a -> a -> a
-: Maybe a
mx
conjureEquality :: Maybe a -> Maybe Expr
conjureEquality Maybe a
mx = Expr -> Expr
from (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
where
x :: a
x = Maybe a -> a
forall a. HasCallStack => Maybe a -> a
fromJust Maybe a
mx
from :: Expr -> Expr
from Expr
e = String -> (Maybe a -> Maybe a -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" Maybe a -> Maybe a -> Bool
(==)
where
.==. :: a -> a -> Bool
(.==.) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
Maybe a
Nothing == :: Maybe a -> Maybe a -> Bool
== Maybe a
Nothing = Bool
True
Maybe a
Nothing == (Just a
_) = Bool
False
(Just a
_) == Maybe a
Nothing = Bool
False
(Just a
x) == (Just a
y) = a
x a -> a -> Bool
.==. a
y
instance ( Conjurable a, Listable a, Show a, Express a
, Conjurable b, Listable b, Show b, Express b
) => Conjurable (Either a b) where
conjureExpress :: Either a b -> Expr -> Expr
conjureExpress = Either a b -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: Either a b -> Maybe [[Expr]]
conjureTiers = Either a b -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: Either a b -> Reification
conjureSubTypes Either a b
elr = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
l Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
r
where
Left a
l = Either a b
elr
Right b
r = Either a b
elr
conjureCases :: Either a b -> [Expr]
conjureCases Either a b
exy = [ String -> (a -> Either a b) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"Left" (a -> Either a b
forall a b. a -> Either a b
Left (a -> Either a b) -> Either a b -> a -> Either a b
forall a b. (a -> b) -> b -> a -> b
->: Either a b
exy) Expr -> Expr -> Expr
:$ Either a b -> Expr
forall a. Typeable a => a -> Expr
hole Either a b
x
, String -> (b -> Either a b) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"Right" (b -> Either a b
forall a b. b -> Either a b
Right (b -> Either a b) -> Either a b -> b -> Either a b
forall a b. (a -> b) -> b -> a -> b
->: Either a b
exy) Expr -> Expr -> Expr
:$ Either a b -> Expr
forall a. Typeable a => a -> Expr
hole Either a b
y
]
where
x :: Either a b
x = a -> Either a b
forall a b. a -> Either a b
Left a
forall a. HasCallStack => a
undefined Either a b -> Either a b -> Either a b
forall a. a -> a -> a
-: Either a b
exy
y :: Either a b
y = b -> Either a b
forall a b. b -> Either a b
Right b
forall a. HasCallStack => a
undefined Either a b -> Either a b -> Either a b
forall a. a -> a -> a
-: Either a b
exy
conjureEquality :: Either a b -> Maybe Expr
conjureEquality Either a b
elr = Expr -> Expr -> Expr
from (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
l Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
r
where
Left a
l = Either a b
elr
Right b
r = Either a b
elr
from :: Expr -> Expr -> Expr
from Expr
el Expr
er = String -> (Either a b -> Either a b -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" Either a b -> Either a b -> Bool
(==)
where
==. :: a -> a -> Bool
(==.) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
el (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
l
.== :: b -> b -> Bool
(.==) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
er (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
r
(Left a
x) == :: Either a b -> Either a b -> Bool
== (Left a
y) = a
x a -> a -> Bool
==. a
y
(Left a
_) == (Right b
_) = Bool
False
(Right b
_) == (Left a
_) = Bool
False
(Right b
x) == (Right b
y) = b
x b -> b -> Bool
.== b
y
instance (Conjurable a, Conjurable b) => Conjurable (a -> b) where
conjureArgumentHoles :: (a -> b) -> [Expr]
conjureArgumentHoles a -> b
f = a -> Expr
forall a. Typeable a => a -> Expr
hole ((a -> b) -> a
forall a b. (a -> b) -> a
argTy a -> b
f) Expr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
: b -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles (a -> b
f a
forall a. HasCallStack => a
undefined)
conjureSubTypes :: (a -> b) -> Reification
conjureSubTypes a -> b
f = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType ((a -> b) -> a
forall a b. (a -> b) -> a
argTy a -> b
f) Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType ((a -> b) -> b
forall a b. (a -> b) -> b
resTy a -> b
f)
conjureIf :: (a -> b) -> Expr
conjureIf a -> b
f = b -> Expr
forall a. Conjurable a => a -> Expr
conjureIf (a -> b
f a
forall a. HasCallStack => a
undefined)
conjureArgumentCases :: (a -> b) -> [[Expr]]
conjureArgumentCases a -> b
f = a -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureCases ((a -> b) -> a
forall a b. (a -> b) -> a
argTy a -> b
f) [Expr] -> [[Expr]] -> [[Expr]]
forall a. a -> [a] -> [a]
: b -> [[Expr]]
forall a. Conjurable a => a -> [[Expr]]
conjureArgumentCases (a -> b
f a
forall a. HasCallStack => a
undefined)
conjureExpress :: (a -> b) -> Expr -> Expr
conjureExpress a -> b
f Expr
e
| Expr -> TypeRep
typ Expr
e TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf ((a -> b) -> a
forall a b. (a -> b) -> a
argTy a -> b
f) = a -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr
conjureExpress ((a -> b) -> a
forall a b. (a -> b) -> a
argTy a -> b
f) Expr
e
| Bool
otherwise = b -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr
conjureExpress (a -> b
f a
forall a. HasCallStack => a
undefined) Expr
e
conjureEvaluate :: (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe (a -> b)
conjureEvaluate Expr -> Expr
exprExpr Int
mx Defn
defn Expr
ef = Maybe (a -> b)
mf
where
ce :: Expr -> Maybe b
ce = (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe b
forall a.
Conjurable a =>
(Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a
conjureEvaluate Expr -> Expr
exprExpr Int
mx Defn
defn
mf :: Maybe (a -> b)
mf = case Expr -> Maybe b
ce (Expr -> Expr
holeAsTypeOf Expr
ef Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
x) Maybe b -> Maybe b -> Maybe b
forall a. a -> a -> a
-: b -> Maybe b
forall a. a -> Maybe a
Just (a -> b
f a
x) of
Maybe b
Nothing -> Maybe (a -> b)
forall a. Maybe a
Nothing
Just b
_ -> (a -> b) -> Maybe (a -> b)
forall a. a -> Maybe a
Just ((a -> b) -> Maybe (a -> b)) -> (a -> b) -> Maybe (a -> b)
forall a b. (a -> b) -> a -> b
$ \a
x -> b -> Maybe b -> b
forall a. a -> Maybe a -> a
fromMaybe b
forall {a}. a
err (Maybe b -> b) -> (Expr -> Maybe b) -> Expr -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Maybe b
ce (Expr -> b) -> Expr -> b
forall a b. (a -> b) -> a -> b
$ Expr
ef Expr -> Expr -> Expr
:$ Expr -> Expr
exprExpr (String -> a -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"" a
x)
f :: a -> b
f = a -> b
forall a. HasCallStack => a
undefined (a -> b) -> (a -> b) -> a -> b
forall a. a -> a -> a
-: Maybe (a -> b) -> a -> b
forall a. HasCallStack => Maybe a -> a
fromJust Maybe (a -> b)
mf
x :: a
x = (a -> b) -> a
forall a b. (a -> b) -> a
argTy a -> b
f
err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"conjureEvaluate (a->b): BUG! This should never be evaluated as it is protected by the outer case."
argTy :: (a -> b) -> a
argTy :: forall a b. (a -> b) -> a
argTy a -> b
_ = a
forall a. HasCallStack => a
undefined
resTy :: (a -> b) -> b
resTy :: forall a b. (a -> b) -> b
resTy a -> b
_ = b
forall a. HasCallStack => a
undefined
cevaluate :: Conjurable f => Int -> Defn -> Maybe f
cevaluate :: forall f. Conjurable f => Int -> Defn -> Maybe f
cevaluate Int
mx Defn
defn = Maybe f
mr
where
mr :: Maybe f
mr = (Expr -> Expr) -> Int -> Defn -> Expr -> Maybe f
forall a.
Conjurable a =>
(Expr -> Expr) -> Int -> Defn -> Expr -> Maybe a
conjureEvaluate Expr -> Expr
exprExpr Int
mx Defn
defn Expr
ef'
exprExpr :: Expr -> Expr
exprExpr = f -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr
conjureExpress (f -> Expr -> Expr) -> f -> Expr -> Expr
forall a b. (a -> b) -> a -> b
$ Maybe f -> f
forall a. HasCallStack => Maybe a -> a
fromJust Maybe f
mr
(Expr
ef':[Expr]
_) = Expr -> [Expr]
unfoldApp (Expr -> [Expr])
-> ((Expr, Expr) -> Expr) -> (Expr, Expr) -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr, Expr) -> Expr
forall a b. (a, b) -> a
fst ((Expr, Expr) -> [Expr]) -> (Expr, Expr) -> [Expr]
forall a b. (a -> b) -> a -> b
$ Defn -> (Expr, Expr)
forall a. HasCallStack => [a] -> a
head Defn
defn
ceval :: Conjurable f => Int -> f -> Defn -> f
ceval :: forall f. Conjurable f => Int -> f -> Defn -> f
ceval Int
mx f
z = f -> Maybe f -> f
forall a. a -> Maybe a -> a
fromMaybe f
z (Maybe f -> f) -> (Defn -> Maybe f) -> Defn -> f
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Defn -> Maybe f
forall f. Conjurable f => Int -> Defn -> Maybe f
cevaluate Int
mx
cevl :: Conjurable f => Int -> Defn -> f
cevl :: forall f. Conjurable f => Int -> Defn -> f
cevl Int
mx = Int -> f -> Defn -> f
forall f. Conjurable f => Int -> f -> Defn -> f
ceval Int
mx f
forall {a}. a
err
where
err :: a
err = String -> a
forall a. HasCallStack => String -> a
error String
"cevl: type mismatch"
conjureApplication :: Conjurable f => String -> f -> Expr
conjureApplication :: forall f. Conjurable f => String -> f -> Expr
conjureApplication = (String -> f -> Expr) -> String -> f -> Expr
forall f.
Conjurable f =>
(String -> f -> Expr) -> String -> f -> Expr
conjureWhatApplication String -> f -> Expr
forall a. Typeable a => String -> a -> Expr
value
conjureVarApplication :: Conjurable f => String -> f -> Expr
conjureVarApplication :: forall f. Conjurable f => String -> f -> Expr
conjureVarApplication = (String -> f -> Expr) -> String -> f -> Expr
forall f.
Conjurable f =>
(String -> f -> Expr) -> String -> f -> Expr
conjureWhatApplication String -> f -> Expr
forall a. Typeable a => String -> a -> Expr
var
conjureWhatApplication :: Conjurable f => (String -> f -> Expr) -> String -> f -> Expr
conjureWhatApplication :: forall f.
Conjurable f =>
(String -> f -> Expr) -> String -> f -> Expr
conjureWhatApplication String -> f -> Expr
what String
nm f
f = Expr -> Expr
mostGeneralCanonicalVariation (Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Expr] -> Expr
foldApp
([Expr] -> Expr) -> [Expr] -> Expr
forall a b. (a -> b) -> a -> b
$ String -> f -> Expr
what String
nf f
f Expr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
: (String -> Expr -> Expr) -> [String] -> [Expr] -> [Expr]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith String -> Expr -> Expr
varAsTypeOf [String]
nas (f -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles f
f)
where
(String
nf:[String]
nas) = String -> [String]
words String
nm [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
forall a. a -> [a]
repeat String
""
conjurePats :: Conjurable f => [Expr] -> String -> f -> [[ [Expr] ]]
conjurePats :: forall f. Conjurable f => [Expr] -> String -> f -> [[[Expr]]]
conjurePats [Expr]
es String
nm f
f = ([[Expr]] -> [Expr]) -> [[[[Expr]]]] -> [[[Expr]]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (([Expr] -> Expr) -> [[Expr]] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map [Expr] -> Expr
mkApp)
([[[[Expr]]]] -> [[[Expr]]]) -> [[[[Expr]]]] -> [[[Expr]]]
forall a b. (a -> b) -> a -> b
$ [[[[Expr]]]] -> [[[[Expr]]]]
combinePatternOptions
([[[[Expr]]]] -> [[[[Expr]]]]) -> [[[[Expr]]]] -> [[[[Expr]]]]
forall a b. (a -> b) -> a -> b
$ [Expr] -> f -> [[[[Expr]]]]
forall f. Conjurable f => [Expr] -> f -> [[[[Expr]]]]
conjureArgumentPats [Expr]
es f
f
where
mkApp :: [Expr] -> Expr
mkApp = [Expr] -> Expr
foldApp ([Expr] -> Expr) -> ([Expr] -> [Expr]) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr
efExpr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
:)
([Expr] -> [Expr]) -> ([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
unfold
(Expr -> [Expr]) -> ([Expr] -> Expr) -> [Expr] -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr
conjureMostGeneralCanonicalVariation f
f
(Expr -> Expr) -> ([Expr] -> Expr) -> [Expr] -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Expr] -> Expr
fold
ef :: Expr
ef = String -> f -> Expr
forall a. Typeable a => String -> a -> Expr
var ([String] -> String
forall a. HasCallStack => [a] -> a
head ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String]
words String
nm) f
f
combinePatternOptions :: [ [[ [Expr] ]] ] -> [[ [[Expr]] ]]
combinePatternOptions :: [[[[Expr]]]] -> [[[[Expr]]]]
combinePatternOptions [] = [[[[]]]]
combinePatternOptions ([[[Expr]]]
esss:[[[[Expr]]]]
essss) = [[[Expr]]] -> [[[[Expr]]]] -> [[[[Expr]]]]
concatPrefixesWithT [[[Expr]]]
esss
([[[[Expr]]]] -> [[[[Expr]]]]) -> [[[[Expr]]]] -> [[[[Expr]]]]
forall a b. (a -> b) -> a -> b
$ [[[[Expr]]]] -> [[[[Expr]]]]
combinePatternOptions [[[[Expr]]]]
essss
concatPrefixesWithT :: [[[Expr]]] -> [[ [[Expr]] ]] -> [[ [[Expr]] ]]
concatPrefixesWithT :: [[[Expr]]] -> [[[[Expr]]]] -> [[[[Expr]]]]
concatPrefixesWithT [[[Expr]]]
esss [[[[Expr]]]]
r = ([Expr] -> [[[[Expr]]]]) -> [[[Expr]]] -> [[[[Expr]]]]
forall a b. (a -> [[b]]) -> [[a]] -> [[b]]
concatMapT ([Expr] -> [[[[Expr]]]] -> [[[[Expr]]]]
`concatPrefixesWith` [[[[Expr]]]]
r) [[[Expr]]]
esss
concatPrefixesWith :: [Expr] -> [[ [[Expr]] ]] -> [[ [[Expr]] ]]
concatPrefixesWith :: [Expr] -> [[[[Expr]]]] -> [[[[Expr]]]]
concatPrefixesWith [Expr]
es [[[[Expr]]]]
r = ([[[Expr]]] -> [[Expr]]) -> [[[[[Expr]]]]] -> [[[[Expr]]]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT [[[Expr]]] -> [[Expr]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[[[Expr]]]]] -> [[[[Expr]]]]) -> [[[[[Expr]]]]] -> [[[[Expr]]]]
forall a b. (a -> b) -> a -> b
$ [[[[[Expr]]]]] -> [[[[[Expr]]]]]
forall a. [[[a]]] -> [[[a]]]
products [Expr -> [[[[Expr]]]] -> [[[[Expr]]]]
prefixWith Expr
e [[[[Expr]]]]
r | Expr
e <- [Expr]
es]
prefixWith :: Expr -> [[ [[Expr]] ]] -> [[ [[Expr]] ]]
prefixWith :: Expr -> [[[[Expr]]]] -> [[[[Expr]]]]
prefixWith Expr
e = ([[Expr]] -> [[Expr]]) -> [[[[Expr]]]] -> [[[[Expr]]]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (([Expr] -> [Expr]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> [a] -> [b]
map (Expr
eExpr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
:))
conjureArgumentPats :: Conjurable f => [Expr] -> f -> [ [[ [Expr] ]] ]
conjureArgumentPats :: forall f. Conjurable f => [Expr] -> f -> [[[[Expr]]]]
conjureArgumentPats [Expr]
es f
f = (Expr -> [Expr] -> [[[Expr]]])
-> [Expr] -> [[Expr]] -> [[[[Expr]]]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Expr -> [Expr] -> [[[Expr]]]
mk (f -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles f
f) (f -> [[Expr]]
forall a. Conjurable a => a -> [[Expr]]
conjureArgumentCases f
f)
where
mk :: Expr -> [Expr] -> [[[Expr]]]
mk Expr
h [] = ([Expr] -> [Expr]) -> [[[Expr]]] -> [[[Expr]]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT ([Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr
h]) ([[[Expr]]] -> [[[Expr]]]) -> [[[Expr]]] -> [[[Expr]]]
forall a b. (a -> b) -> a -> b
$ [[Expr]] -> [[[Expr]]]
forall a. [[a]] -> [[[a]]]
setsOf [[Expr
e] | Expr
e <- [Expr]
es, Expr -> TypeRep
typ Expr
e TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
h]
mk Expr
h [Expr]
cs = [[[Expr
h]], [[Expr]
cs]]
prods :: [[a]] -> [[a]]
prods :: forall a. [[a]] -> [[a]]
prods = ([a] -> [[a]] -> [[a]]) -> [[a]] -> [[a]] -> [[a]]
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((a -> [a] -> [a]) -> [a] -> [[a]] -> [[a]]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
productWith (:)) [[]]
where
productWith :: (t -> t -> a) -> [t] -> [t] -> [a]
productWith t -> t -> a
(?) [t]
xs [t]
ys = [t
x t -> t -> a
? t
y | t
x <- [t]
xs, t
y <- [t]
ys]
instance Conjurable Ordering where
conjureExpress :: Ordering -> Expr -> Expr
conjureExpress = Ordering -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Ordering -> Maybe Expr
conjureEquality = Ordering -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Ordering -> Maybe [[Expr]]
conjureTiers = Ordering -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
instance Conjurable Float where
conjureExpress :: Float -> Expr -> Expr
conjureExpress = Float -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Float -> Maybe Expr
conjureEquality = Float -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Float -> Maybe [[Expr]]
conjureTiers = Float -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Float -> Int
conjureSize = Float -> Int
forall b. Integral b => Float -> b
forall a b. (RealFrac a, Integral b) => a -> b
round
instance Conjurable Double where
conjureExpress :: Double -> Expr -> Expr
conjureExpress = Double -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Double -> Maybe Expr
conjureEquality = Double -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Double -> Maybe [[Expr]]
conjureTiers = Double -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Double -> Int
conjureSize = Double -> Int
forall b. Integral b => Double -> b
forall a b. (RealFrac a, Integral b) => a -> b
round
instance Conjurable Int8 where
conjureExpress :: Int8 -> Expr -> Expr
conjureExpress = Int8 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Int8 -> Maybe Expr
conjureEquality = Int8 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Int8 -> Maybe [[Expr]]
conjureTiers = Int8 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Int8 -> Int
conjureSize = Int8 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Int16 where
conjureExpress :: Int16 -> Expr -> Expr
conjureExpress = Int16 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Int16 -> Maybe Expr
conjureEquality = Int16 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Int16 -> Maybe [[Expr]]
conjureTiers = Int16 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Int16 -> Int
conjureSize = Int16 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Int32 where
conjureExpress :: Int32 -> Expr -> Expr
conjureExpress = Int32 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Int32 -> Maybe Expr
conjureEquality = Int32 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Int32 -> Maybe [[Expr]]
conjureTiers = Int32 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Int32 -> Int
conjureSize = Int32 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Int64 where
conjureExpress :: Int64 -> Expr -> Expr
conjureExpress = Int64 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Int64 -> Maybe Expr
conjureEquality = Int64 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Int64 -> Maybe [[Expr]]
conjureTiers = Int64 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Int64 -> Int
conjureSize = Int64 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Word where
conjureExpress :: Word -> Expr -> Expr
conjureExpress = Word -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Word -> Maybe Expr
conjureEquality = Word -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Word -> Maybe [[Expr]]
conjureTiers = Word -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Word -> Int
conjureSize = Word -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Word8 where
conjureExpress :: Word8 -> Expr -> Expr
conjureExpress = Word8 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Word8 -> Maybe Expr
conjureEquality = Word8 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Word8 -> Maybe [[Expr]]
conjureTiers = Word8 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Word8 -> Int
conjureSize = Word8 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Word16 where
conjureExpress :: Word16 -> Expr -> Expr
conjureExpress = Word16 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Word16 -> Maybe Expr
conjureEquality = Word16 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Word16 -> Maybe [[Expr]]
conjureTiers = Word16 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Word16 -> Int
conjureSize = Word16 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Word32 where
conjureExpress :: Word32 -> Expr -> Expr
conjureExpress = Word32 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Word32 -> Maybe Expr
conjureEquality = Word32 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Word32 -> Maybe [[Expr]]
conjureTiers = Word32 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Word32 -> Int
conjureSize = Word32 -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable Word64 where
conjureExpress :: Word64 -> Expr -> Expr
conjureExpress = Word64 -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Word64 -> Maybe Expr
conjureEquality = Word64 -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Word64 -> Maybe [[Expr]]
conjureTiers = Word64 -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Word64 -> Int
conjureSize = Word64 -> Int
forall a. Integral a => a -> Int
integralSize
instance (Integral a, Conjurable a, Listable a, Show a, Eq a, Express a) => Conjurable (Ratio a) where
conjureExpress :: Ratio a -> Expr -> Expr
conjureExpress = Ratio a -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Ratio a -> Maybe Expr
conjureEquality = Ratio a -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Ratio a -> Maybe [[Expr]]
conjureTiers = Ratio a -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Ratio a -> Int
conjureSize Ratio a
q = a -> Int
forall a. Conjurable a => a -> Int
conjureSize (Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
q) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Conjurable a => a -> Int
conjureSize (Ratio a -> a
forall a. Ratio a -> a
denominator Ratio a
q)
conjureSubTypes :: Ratio a -> Reification
conjureSubTypes Ratio a
q = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType (Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
q)
conjureCases :: Ratio a -> [Expr]
conjureCases Ratio a
q = [String -> (a -> a -> Ratio a) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"%" (a -> a -> Ratio a
forall a. Integral a => a -> a -> Ratio a
(%) (a -> a -> Ratio a) -> Ratio a -> a -> a -> Ratio a
forall a b c. (a -> b -> c) -> c -> a -> b -> c
->>: Ratio a
q) Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
n Expr -> Expr -> Expr
:$ a -> Expr
forall a. Typeable a => a -> Expr
hole a
d]
where
n :: a
n = Ratio a -> a
forall a. Ratio a -> a
numerator Ratio a
q
d :: a
d = Ratio a -> a
forall a. Ratio a -> a
denominator Ratio a
q
instance (RealFloat a, Conjurable a, Listable a, Show a, Eq a, Express a) => Conjurable (Complex a) where
conjureExpress :: Complex a -> Expr -> Expr
conjureExpress = Complex a -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: Complex a -> Maybe Expr
conjureEquality = Complex a -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: Complex a -> Maybe [[Expr]]
conjureTiers = Complex a -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: Complex a -> Int
conjureSize Complex a
x = a -> Int
forall a. Conjurable a => a -> Int
conjureSize (Complex a -> a
forall a. Complex a -> a
realPart Complex a
x) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ a -> Int
forall a. Conjurable a => a -> Int
conjureSize (Complex a -> a
forall a. Complex a -> a
imagPart Complex a
x)
conjureSubTypes :: Complex a -> Reification
conjureSubTypes Complex a
x = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType (Complex a -> a
forall a. Complex a -> a
realPart Complex a
x)
instance Conjurable A where
conjureExpress :: A -> Expr -> Expr
conjureExpress = A -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: A -> Maybe Expr
conjureEquality = A -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: A -> Maybe [[Expr]]
conjureTiers = A -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: A -> Int
conjureSize = A -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable B where
conjureExpress :: B -> Expr -> Expr
conjureExpress = B -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: B -> Maybe Expr
conjureEquality = B -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: B -> Maybe [[Expr]]
conjureTiers = B -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: B -> Int
conjureSize = B -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable C where
conjureExpress :: C -> Expr -> Expr
conjureExpress = C -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: C -> Maybe Expr
conjureEquality = C -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: C -> Maybe [[Expr]]
conjureTiers = C -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: C -> Int
conjureSize = C -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable D where
conjureExpress :: D -> Expr -> Expr
conjureExpress = D -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: D -> Maybe Expr
conjureEquality = D -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: D -> Maybe [[Expr]]
conjureTiers = D -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: D -> Int
conjureSize = D -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable E where
conjureExpress :: E -> Expr -> Expr
conjureExpress = E -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: E -> Maybe Expr
conjureEquality = E -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: E -> Maybe [[Expr]]
conjureTiers = E -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: E -> Int
conjureSize = E -> Int
forall a. Integral a => a -> Int
integralSize
instance Conjurable F where
conjureExpress :: F -> Expr -> Expr
conjureExpress = F -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureEquality :: F -> Maybe Expr
conjureEquality = F -> Maybe Expr
forall a. (Eq a, Typeable a) => a -> Maybe Expr
reifyEquality
conjureTiers :: F -> Maybe [[Expr]]
conjureTiers = F -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSize :: F -> Int
conjureSize = F -> Int
forall a. Integral a => a -> Int
integralSize
instance ( 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) where
conjureExpress :: (a, b, c, d) -> Expr -> Expr
conjureExpress = (a, b, c, d) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d) -> Reification
conjureSubTypes (a, b, c, d)
xyzw = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
where (a
x,b
y,c
z,d
w) = (a, b, c, d)
xyzw
conjureEquality :: (a, b, c, d) -> Maybe Expr
conjureEquality (a, b, c, d)
xyzw = Expr -> Expr -> Expr -> Expr -> Expr
from
(Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
where
(a
x,b
y,c
z,d
w) = (a, b, c, d)
xyzw
from :: Expr -> Expr -> Expr -> Expr -> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 = String -> ((a, b, c, d) -> (a, b, c, d) -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d) -> (a, b, c, d) -> Bool
(==)
where
==... :: a -> a -> Bool
(==...) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==.. :: b -> b -> Bool
(.==..) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==. :: c -> c -> Bool
(..==.) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...== :: d -> d -> Bool
(...==) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
(a
x1,b
y1,c
z1,d
w1) == :: (a, b, c, d) -> (a, b, c, d) -> Bool
== (a
x2,b
y2,c
z2,d
w2) = a
x1 a -> a -> Bool
==... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==.. b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==. c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...== d
w2
instance ( 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) where
conjureExpress :: (a, b, c, d, e) -> Expr -> Expr
conjureExpress = (a, b, c, d, e) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e) -> Reification
conjureSubTypes (a, b, c, d, e)
xyzwv = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
where (a
x,b
y,c
z,d
w,e
v) = (a, b, c, d, e)
xyzwv
conjureEquality :: (a, b, c, d, e) -> Maybe Expr
conjureEquality (a, b, c, d, e)
xyzwv = Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
where
(a
x,b
y,c
z,d
w,e
v) = (a, b, c, d, e)
xyzwv
from :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 = String -> ((a, b, c, d, e) -> (a, b, c, d, e) -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e) -> (a, b, c, d, e) -> Bool
(==)
where
==.... :: a -> a -> Bool
(==....) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==... :: b -> b -> Bool
(.==...) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==.. :: c -> c -> Bool
(..==..) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==. :: d -> d -> Bool
(...==.) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....== :: e -> e -> Bool
(....==) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
(a
x1,b
y1,c
z1,d
w1,e
v1) == :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2) = a
x1 a -> a -> Bool
==.... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==.. c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==. d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....== e
v2
instance ( 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) where
conjureExpress :: (a, b, c, d, e, f) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f) -> Reification
conjureSubTypes (a, b, c, d, e, f)
xyzwvu = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
where (a
x,b
y,c
z,d
w,e
v,f
u) = (a, b, c, d, e, f)
xyzwvu
conjureEquality :: (a, b, c, d, e, f) -> Maybe Expr
conjureEquality (a, b, c, d, e, f)
xyzwvu = Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
where
(a
x,b
y,c
z,d
w,e
v,f
u) = (a, b, c, d, e, f)
xyzwvu
from :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 = String
-> ((a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool
(==)
where
==..... :: a -> a -> Bool
(==.....) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==.... :: b -> b -> Bool
(.==....) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==... :: c -> c -> Bool
(..==...) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==.. :: d -> d -> Bool
(...==..) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==. :: e -> e -> Bool
(....==.) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....== :: f -> f -> Bool
(.....==) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1) == :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2) = a
x1 a -> a -> Bool
==..... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==.... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==... c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==.. d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==. e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....== f
u2
instance ( 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) where
conjureExpress :: (a, b, c, d, e, f, g) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f, g) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f, g) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f, g) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f, g) -> Reification
conjureSubTypes (a, b, c, d, e, f, g)
xyzwvut = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g -> Reification
forall a. Conjurable a => a -> Reification
conjureType g
t
where (a
x,b
y,c
z,d
w,e
v,f
u,g
t) = (a, b, c, d, e, f, g)
xyzwvut
conjureEquality :: (a, b, c, d, e, f, g) -> Maybe Expr
conjureEquality (a, b, c, d, e, f, g)
xyzwvut = Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality g
t
where
(a
x,b
y,c
z,d
w,e
v,f
u,g
t) = (a, b, c, d, e, f, g)
xyzwvut
from :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 Expr
e7 = String
-> ((a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool) -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool
(==)
where
==...... :: a -> a -> Bool
(==......) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==..... :: b -> b -> Bool
(.==.....) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==.... :: c -> c -> Bool
(..==....) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==... :: d -> d -> Bool
(...==...) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==.. :: e -> e -> Bool
(....==..) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....==. :: f -> f -> Bool
(.....==.) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
......== :: g -> g -> Bool
(......==) = Expr -> g -> g -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e7 (g -> g -> Bool) -> g -> g -> g -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: g
t
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1,g
t1) == :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2,g
t2) = a
x1 a -> a -> Bool
==...... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==..... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==.... c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==... d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==.. e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....==. f
u2
Bool -> Bool -> Bool
&& g
t1 g -> g -> Bool
......== g
t2
instance ( 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 h, Listable h, Show h, Express h
) => Conjurable (a,b,c,d,e,f,g,h) where
conjureExpress :: (a, b, c, d, e, f, g, h) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f, g, h) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f, g, h) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f, g, h) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f, g, h) -> Reification
conjureSubTypes (a, b, c, d, e, f, g, h)
xyzwvuts = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g -> Reification
forall a. Conjurable a => a -> Reification
conjureType g
t
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. h -> Reification
forall a. Conjurable a => a -> Reification
conjureType h
s
where (a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s) = (a, b, c, d, e, f, g, h)
xyzwvuts
conjureEquality :: (a, b, c, d, e, f, g, h) -> Maybe Expr
conjureEquality (a, b, c, d, e, f, g, h)
xyzwvuts = Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality g
t
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> h -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality h
s
where
(a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s) = (a, b, c, d, e, f, g, h)
xyzwvuts
from :: Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 Expr
e7 Expr
e8 = String
-> ((a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool)
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool
(==)
where
==....... :: a -> a -> Bool
(==.......) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==...... :: b -> b -> Bool
(.==......) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==..... :: c -> c -> Bool
(..==.....) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==.... :: d -> d -> Bool
(...==....) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==... :: e -> e -> Bool
(....==...) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....==.. :: f -> f -> Bool
(.....==..) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
......==. :: g -> g -> Bool
(......==.) = Expr -> g -> g -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e7 (g -> g -> Bool) -> g -> g -> g -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: g
t
.......== :: h -> h -> Bool
(.......==) = Expr -> h -> h -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e8 (h -> h -> Bool) -> h -> h -> h -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: h
s
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1,g
t1,h
s1) == :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2,g
t2,h
s2) = a
x1 a -> a -> Bool
==....... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==...... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==..... c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==.... d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==... e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....==.. f
u2
Bool -> Bool -> Bool
&& g
t1 g -> g -> Bool
......==. g
t2
Bool -> Bool -> Bool
&& h
s1 h -> h -> Bool
.......== h
s2
instance ( 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 h, Listable h, Show h, Express h
, Conjurable i, Listable i, Show i, Express i
) => Conjurable (a,b,c,d,e,f,g,h,i) where
conjureExpress :: (a, b, c, d, e, f, g, h, i) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f, g, h, i) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f, g, h, i) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f, g, h, i) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f, g, h, i) -> Reification
conjureSubTypes (a, b, c, d, e, f, g, h, i)
xyzwvutsr = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g -> Reification
forall a. Conjurable a => a -> Reification
conjureType g
t
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. h -> Reification
forall a. Conjurable a => a -> Reification
conjureType h
s
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Reification
forall a. Conjurable a => a -> Reification
conjureType i
r
where (a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r) = (a, b, c, d, e, f, g, h, i)
xyzwvutsr
conjureEquality :: (a, b, c, d, e, f, g, h, i) -> Maybe Expr
conjureEquality (a, b, c, d, e, f, g, h, i)
xyzwvutsr = Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality g
t
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> h -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality h
s
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> i -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality i
r
where
(a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r) = (a, b, c, d, e, f, g, h, i)
xyzwvutsr
from :: Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 Expr
e7 Expr
e8 Expr
e9 = String
-> ((a, b, c, d, e, f, g, h, i)
-> (a, b, c, d, e, f, g, h, i) -> Bool)
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool
(==)
where
==........ :: a -> a -> Bool
(==........) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==....... :: b -> b -> Bool
(.==.......) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==...... :: c -> c -> Bool
(..==......) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==..... :: d -> d -> Bool
(...==.....) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==.... :: e -> e -> Bool
(....==....) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....==... :: f -> f -> Bool
(.....==...) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
......==.. :: g -> g -> Bool
(......==..) = Expr -> g -> g -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e7 (g -> g -> Bool) -> g -> g -> g -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: g
t
.......==. :: h -> h -> Bool
(.......==.) = Expr -> h -> h -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e8 (h -> h -> Bool) -> h -> h -> h -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: h
s
........== :: i -> i -> Bool
(........==) = Expr -> i -> i -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e9 (i -> i -> Bool) -> i -> i -> i -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: i
r
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1,g
t1,h
s1,i
r1) == :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2,g
t2,h
s2,i
r2) = a
x1 a -> a -> Bool
==........ a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==....... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==...... c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==..... d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==.... e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....==... f
u2
Bool -> Bool -> Bool
&& g
t1 g -> g -> Bool
......==.. g
t2
Bool -> Bool -> Bool
&& h
s1 h -> h -> Bool
.......==. h
s2
Bool -> Bool -> Bool
&& i
r1 i -> i -> Bool
........== i
r2
instance ( 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 h, Listable h, Show h, Express h
, Conjurable i, Listable i, Show i, Express i
, Conjurable j, Listable j, Show j, Express j
) => Conjurable (a,b,c,d,e,f,g,h,i,j) where
conjureExpress :: (a, b, c, d, e, f, g, h, i, j) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f, g, h, i, j) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f, g, h, i, j) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f, g, h, i, j) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f, g, h, i, j) -> Reification
conjureSubTypes (a, b, c, d, e, f, g, h, i, j)
xyzwvutsrq = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g -> Reification
forall a. Conjurable a => a -> Reification
conjureType g
t
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. h -> Reification
forall a. Conjurable a => a -> Reification
conjureType h
s
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Reification
forall a. Conjurable a => a -> Reification
conjureType i
r
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Reification
forall a. Conjurable a => a -> Reification
conjureType j
q
where (a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r,j
q) = (a, b, c, d, e, f, g, h, i, j)
xyzwvutsrq
conjureEquality :: (a, b, c, d, e, f, g, h, i, j) -> Maybe Expr
conjureEquality (a, b, c, d, e, f, g, h, i, j)
xyzwvutsrq = Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality g
t
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> h -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality h
s
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> i -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality i
r
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> j -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality j
q
where
(a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r,j
q) = (a, b, c, d, e, f, g, h, i, j)
xyzwvutsrq
from :: Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 Expr
e7 Expr
e8 Expr
e9 Expr
e10 = String
-> ((a, b, c, d, e, f, g, h, i, j)
-> (a, b, c, d, e, f, g, h, i, j) -> Bool)
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f, g, h, i, j)
-> (a, b, c, d, e, f, g, h, i, j) -> Bool
(==)
where
==......... :: a -> a -> Bool
(==.........) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==........ :: b -> b -> Bool
(.==........) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==....... :: c -> c -> Bool
(..==.......) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==...... :: d -> d -> Bool
(...==......) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==..... :: e -> e -> Bool
(....==.....) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....==.... :: f -> f -> Bool
(.....==....) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
......==... :: g -> g -> Bool
(......==...) = Expr -> g -> g -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e7 (g -> g -> Bool) -> g -> g -> g -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: g
t
.......==.. :: h -> h -> Bool
(.......==..) = Expr -> h -> h -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e8 (h -> h -> Bool) -> h -> h -> h -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: h
s
........==. :: i -> i -> Bool
(........==.) = Expr -> i -> i -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e9 (i -> i -> Bool) -> i -> i -> i -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: i
r
.........== :: j -> j -> Bool
(.........==) = Expr -> j -> j -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e10 (j -> j -> Bool) -> j -> j -> j -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: j
q
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1,g
t1,h
s1,i
r1,j
q1) == :: (a, b, c, d, e, f, g, h, i, j)
-> (a, b, c, d, e, f, g, h, i, j) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2,g
t2,h
s2,i
r2,j
q2) = a
x1 a -> a -> Bool
==......... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==........ b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==....... c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==...... d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==..... e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....==.... f
u2
Bool -> Bool -> Bool
&& g
t1 g -> g -> Bool
......==... g
t2
Bool -> Bool -> Bool
&& h
s1 h -> h -> Bool
.......==.. h
s2
Bool -> Bool -> Bool
&& i
r1 i -> i -> Bool
........==. i
r2
Bool -> Bool -> Bool
&& j
q1 j -> j -> Bool
.........== j
q2
instance ( 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 h, Listable h, Show h, Express h
, Conjurable i, Listable i, Show i, Express i
, Conjurable j, Listable j, Show j, Express j
, Conjurable k, Listable k, Show k, Express k
) => Conjurable (a,b,c,d,e,f,g,h,i,j,k) where
conjureExpress :: (a, b, c, d, e, f, g, h, i, j, k) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f, g, h, i, j, k) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f, g, h, i, j, k) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f, g, h, i, j, k) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f, g, h, i, j, k) -> Reification
conjureSubTypes (a, b, c, d, e, f, g, h, i, j, k)
xyzwvutsrqp = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g -> Reification
forall a. Conjurable a => a -> Reification
conjureType g
t
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. h -> Reification
forall a. Conjurable a => a -> Reification
conjureType h
s
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Reification
forall a. Conjurable a => a -> Reification
conjureType i
r
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Reification
forall a. Conjurable a => a -> Reification
conjureType j
q
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. k -> Reification
forall a. Conjurable a => a -> Reification
conjureType k
p
where (a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r,j
q,k
p) = (a, b, c, d, e, f, g, h, i, j, k)
xyzwvutsrqp
conjureEquality :: (a, b, c, d, e, f, g, h, i, j, k) -> Maybe Expr
conjureEquality (a, b, c, d, e, f, g, h, i, j, k)
xyzwvutsrqp = Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality g
t
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> h -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality h
s
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> i -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality i
r
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> j -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality j
q
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> k -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality k
p
where
(a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r,j
q,k
p) = (a, b, c, d, e, f, g, h, i, j, k)
xyzwvutsrqp
from :: Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 Expr
e7 Expr
e8 Expr
e9 Expr
e10 Expr
e11 = String
-> ((a, b, c, d, e, f, g, h, i, j, k)
-> (a, b, c, d, e, f, g, h, i, j, k) -> Bool)
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f, g, h, i, j, k)
-> (a, b, c, d, e, f, g, h, i, j, k) -> Bool
(==)
where
==.......... :: a -> a -> Bool
(==..........) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==......... :: b -> b -> Bool
(.==.........) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==........ :: c -> c -> Bool
(..==........) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==....... :: d -> d -> Bool
(...==.......) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==...... :: e -> e -> Bool
(....==......) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....==..... :: f -> f -> Bool
(.....==.....) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
......==.... :: g -> g -> Bool
(......==....) = Expr -> g -> g -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e7 (g -> g -> Bool) -> g -> g -> g -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: g
t
.......==... :: h -> h -> Bool
(.......==...) = Expr -> h -> h -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e8 (h -> h -> Bool) -> h -> h -> h -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: h
s
........==.. :: i -> i -> Bool
(........==..) = Expr -> i -> i -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e9 (i -> i -> Bool) -> i -> i -> i -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: i
r
.........==. :: j -> j -> Bool
(.........==.) = Expr -> j -> j -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e10 (j -> j -> Bool) -> j -> j -> j -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: j
q
..........== :: k -> k -> Bool
(..........==) = Expr -> k -> k -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e11 (k -> k -> Bool) -> k -> k -> k -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: k
p
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1,g
t1,h
s1,i
r1,j
q1,k
p1) == :: (a, b, c, d, e, f, g, h, i, j, k)
-> (a, b, c, d, e, f, g, h, i, j, k) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2,g
t2,h
s2,i
r2,j
q2,k
p2) = a
x1 a -> a -> Bool
==.......... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==......... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==........ c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==....... d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==...... e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....==..... f
u2
Bool -> Bool -> Bool
&& g
t1 g -> g -> Bool
......==.... g
t2
Bool -> Bool -> Bool
&& h
s1 h -> h -> Bool
.......==... h
s2
Bool -> Bool -> Bool
&& i
r1 i -> i -> Bool
........==.. i
r2
Bool -> Bool -> Bool
&& j
q1 j -> j -> Bool
.........==. j
q2
Bool -> Bool -> Bool
&& k
p1 k -> k -> Bool
..........== k
p2
instance ( 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 h, Listable h, Show h, Express h
, Conjurable i, Listable i, Show i, Express i
, Conjurable j, Listable j, Show j, Express j
, Conjurable k, Listable k, Show k, Express k
, Conjurable l, Listable l, Show l, Express l
) => Conjurable (a,b,c,d,e,f,g,h,i,j,k,l) where
conjureExpress :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr -> Expr
conjureExpress = (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr -> Expr
forall a. (Express a, Show a) => a -> Expr -> Expr
reifyExpress
conjureTiers :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Maybe [[Expr]]
conjureTiers = (a, b, c, d, e, f, g, h, i, j, k, l) -> Maybe [[Expr]]
forall a. (Listable a, Show a, Typeable a) => a -> Maybe [[Expr]]
reifyTiers
conjureSubTypes :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Reification
conjureSubTypes (a, b, c, d, e, f, g, h, i, j, k, l)
xyzwvutsrqpo = a -> Reification
forall a. Conjurable a => a -> Reification
conjureType a
x
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Reification
forall a. Conjurable a => a -> Reification
conjureType b
y
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. c -> Reification
forall a. Conjurable a => a -> Reification
conjureType c
z
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. d -> Reification
forall a. Conjurable a => a -> Reification
conjureType d
w
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> Reification
forall a. Conjurable a => a -> Reification
conjureType e
v
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Reification
forall a. Conjurable a => a -> Reification
conjureType f
u
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. g -> Reification
forall a. Conjurable a => a -> Reification
conjureType g
t
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. h -> Reification
forall a. Conjurable a => a -> Reification
conjureType h
s
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> Reification
forall a. Conjurable a => a -> Reification
conjureType i
r
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. j -> Reification
forall a. Conjurable a => a -> Reification
conjureType j
q
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. k -> Reification
forall a. Conjurable a => a -> Reification
conjureType k
p
Reification -> Reification -> Reification
forall b c a. (b -> c) -> (a -> b) -> a -> c
. l -> Reification
forall a. Conjurable a => a -> Reification
conjureType l
o
where (a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r,j
q,k
p,l
o) = (a, b, c, d, e, f, g, h, i, j, k, l)
xyzwvutsrqpo
conjureEquality :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Maybe Expr
conjureEquality (a, b, c, d, e, f, g, h, i, j, k, l)
xyzwvutsrqpo = Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality a
x
Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality b
y
Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> c -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality c
z
Maybe
(Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr)
-> Maybe Expr
-> Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> d -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality d
w
Maybe
(Expr
-> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> e -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality e
v
Maybe
(Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> f -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality f
u
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr
-> Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality g
t
Maybe (Expr -> Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> h -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality h
s
Maybe (Expr -> Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> i -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality i
r
Maybe (Expr -> Expr -> Expr -> Expr)
-> Maybe Expr -> Maybe (Expr -> Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> j -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality j
q
Maybe (Expr -> Expr -> Expr) -> Maybe Expr -> Maybe (Expr -> Expr)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> k -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality k
p
Maybe (Expr -> Expr) -> Maybe Expr -> Maybe Expr
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> l -> Maybe Expr
forall a. Conjurable a => a -> Maybe Expr
conjureEquality l
o
where
(a
x,b
y,c
z,d
w,e
v,f
u,g
t,h
s,i
r,j
q,k
p,l
o) = (a, b, c, d, e, f, g, h, i, j, k, l)
xyzwvutsrqpo
from :: Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
-> Expr
from Expr
e1 Expr
e2 Expr
e3 Expr
e4 Expr
e5 Expr
e6 Expr
e7 Expr
e8 Expr
e9 Expr
e10 Expr
e11 Expr
e12 = String
-> ((a, b, c, d, e, f, g, h, i, j, k, l)
-> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool)
-> Expr
forall a. Typeable a => String -> a -> Expr
value String
"==" (a, b, c, d, e, f, g, h, i, j, k, l)
-> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool
(==)
where
==........... :: a -> a -> Bool
(==...........) = Expr -> a -> a -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e1 (a -> a -> Bool) -> a -> a -> a -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: a
x
.==.......... :: b -> b -> Bool
(.==..........) = Expr -> b -> b -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e2 (b -> b -> Bool) -> b -> b -> b -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: b
y
..==......... :: c -> c -> Bool
(..==.........) = Expr -> c -> c -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e3 (c -> c -> Bool) -> c -> c -> c -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: c
z
...==........ :: d -> d -> Bool
(...==........) = Expr -> d -> d -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e4 (d -> d -> Bool) -> d -> d -> d -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: d
w
....==....... :: e -> e -> Bool
(....==.......) = Expr -> e -> e -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e5 (e -> e -> Bool) -> e -> e -> e -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: e
v
.....==...... :: f -> f -> Bool
(.....==......) = Expr -> f -> f -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e6 (f -> f -> Bool) -> f -> f -> f -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: f
u
......==..... :: g -> g -> Bool
(......==.....) = Expr -> g -> g -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e7 (g -> g -> Bool) -> g -> g -> g -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: g
t
.......==.... :: h -> h -> Bool
(.......==....) = Expr -> h -> h -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e8 (h -> h -> Bool) -> h -> h -> h -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: h
s
........==... :: i -> i -> Bool
(........==...) = Expr -> i -> i -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e9 (i -> i -> Bool) -> i -> i -> i -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: i
r
.........==.. :: j -> j -> Bool
(.........==..) = Expr -> j -> j -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e10 (j -> j -> Bool) -> j -> j -> j -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: j
q
..........==. :: k -> k -> Bool
(..........==.) = Expr -> k -> k -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e11 (k -> k -> Bool) -> k -> k -> k -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: k
p
...........== :: l -> l -> Bool
(...........==) = Expr -> l -> l -> Bool
forall a. Typeable a => Expr -> a
evl Expr
e12 (l -> l -> Bool) -> l -> l -> l -> Bool
forall a. (a -> a -> Bool) -> a -> a -> a -> Bool
==: l
o
(a
x1,b
y1,c
z1,d
w1,e
v1,f
u1,g
t1,h
s1,i
r1,j
q1,k
p1,l
o1) == :: (a, b, c, d, e, f, g, h, i, j, k, l)
-> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool
== (a
x2,b
y2,c
z2,d
w2,e
v2,f
u2,g
t2,h
s2,i
r2,j
q2,k
p2,l
o2) = a
x1 a -> a -> Bool
==........... a
x2
Bool -> Bool -> Bool
&& b
y1 b -> b -> Bool
.==.......... b
y2
Bool -> Bool -> Bool
&& c
z1 c -> c -> Bool
..==......... c
z2
Bool -> Bool -> Bool
&& d
w1 d -> d -> Bool
...==........ d
w2
Bool -> Bool -> Bool
&& e
v1 e -> e -> Bool
....==....... e
v2
Bool -> Bool -> Bool
&& f
u1 f -> f -> Bool
.....==...... f
u2
Bool -> Bool -> Bool
&& g
t1 g -> g -> Bool
......==..... g
t2
Bool -> Bool -> Bool
&& h
s1 h -> h -> Bool
.......==.... h
s2
Bool -> Bool -> Bool
&& i
r1 i -> i -> Bool
........==... i
r2
Bool -> Bool -> Bool
&& j
q1 j -> j -> Bool
.........==.. j
q2
Bool -> Bool -> Bool
&& k
p1 k -> k -> Bool
..........==. k
p2
Bool -> Bool -> Bool
&& l
o1 l -> l -> Bool
...........== l
o2
instance Name A
instance Name B
instance Name C
instance Name D
instance Name E
instance Name F