module Conjure.Prim
( Prim (..)
, prim
, pr
, prif
, primOrdCaseFor
, cjHoles
, cjTiersFor
, cjAreEqual
, cjMkEquation
)
where
import Conjure.Conjurable
import Conjure.Expr
import Conjure.Utils
import Test.LeanCheck.Error (errorToFalse)
import Test.LeanCheck.Utils
import Test.Speculate.Expr
type Prim = (Expr, Reification)
pr :: (Conjurable a, Show a) => a -> Prim
pr :: forall a. (Conjurable a, Show a) => a -> Prim
pr a
x = (forall a. (Typeable a, Show a) => a -> Expr
val a
x, 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 = (forall a. Typeable a => String -> a -> Expr
value String
s a
x, forall a. Conjurable a => a -> Reification
conjureType a
x)
prif :: Conjurable a => a -> Prim
prif :: forall a. Conjurable a => a -> Prim
prif a
x = (forall a. Typeable a => a -> Expr
ifFor a
x, forall a. Conjurable a => a -> Reification
conjureType a
x)
primOrdCaseFor :: Conjurable a => a -> Prim
primOrdCaseFor :: forall a. Conjurable a => a -> Prim
primOrdCaseFor a
x = (forall a. Typeable a => a -> Expr
caseForOrd a
x, forall a. Conjurable a => a -> Reification
conjureType a
x)
cjReification :: [Prim] -> [Reification1]
cjReification :: [Prim] -> [Reification1]
cjReification [Prim]
ps = forall b a. Eq b => (a -> b) -> [a] -> [a]
nubOn (\(Expr
eh,Maybe Expr
_,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) -> Expr
eh)
forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) forall a. a -> a
id (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd [Prim]
ps) [forall a. Conjurable a => a -> Reification1
conjureReification1 Bool
bool]
cjHoles :: [Prim] -> [Expr]
cjHoles :: [Prim] -> [Expr]
cjHoles [Prim]
ps = [Expr
eh | (Expr
eh,Maybe Expr
_,Just [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- [Prim] -> [Reification1]
cjReification [Prim]
ps]
cjMkEquation :: [Prim] -> Expr -> Expr -> Expr
cjMkEquation :: [Prim] -> Expr -> Expr -> Expr
cjMkEquation [Prim]
ps = [Expr] -> Expr -> Expr -> Expr
mkEquation [Expr
eq | (Expr
_,Just Expr
eq,Maybe [[Expr]]
_,[String]
_,Bool
_,Expr
_) <- [Prim] -> [Reification1]
cjReification [Prim]
ps]
cjAreEqual :: [Prim] -> Int -> Expr -> Expr -> Bool
cjAreEqual :: [Prim] -> Int -> Expr -> Expr -> Bool
cjAreEqual [Prim]
ps Int
maxTests = Expr -> Expr -> Bool
(===)
where
-==- :: Expr -> Expr -> Expr
(-==-) = [Prim] -> Expr -> Expr -> Expr
cjMkEquation [Prim]
ps
Expr
e1 === :: Expr -> Expr -> Bool
=== Expr
e2 = Expr -> Bool
isTrue forall a b. (a -> b) -> a -> b
$ Expr
e1 Expr -> Expr -> Expr
-==- Expr
e2
isTrue :: Expr -> Bool
isTrue = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Bool -> Bool
errorToFalse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Typeable a => a -> Expr -> a
eval Bool
False) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
gs
gs :: Expr -> [Expr]
gs = forall a. Int -> [a] -> [a]
take Int
maxTests forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> [[Expr]]) -> Expr -> [Expr]
grounds ([Prim] -> Expr -> [[Expr]]
cjTiersFor [Prim]
ps)
cjTiersFor :: [Prim] -> Expr -> [[Expr]]
cjTiersFor :: [Prim] -> Expr -> [[Expr]]
cjTiersFor [Prim]
ps Expr
e = [[[Expr]]] -> [[Expr]]
tf [[[Expr]]]
allTiers
where
allTiers :: [ [[Expr]] ]
allTiers :: [[[Expr]]]
allTiers = [[[Expr]]
etiers | (Expr
_,Maybe Expr
_,Just [[Expr]]
etiers,[String]
_,Bool
_,Expr
_) <- [Prim] -> [Reification1]
cjReification [Prim]
ps]
tf :: [[[Expr]]] -> [[Expr]]
tf [] = [[Expr
e]]
tf ([[Expr]]
etiers:[[[Expr]]]
etc) = case [[Expr]]
etiers of
((Expr
e':[Expr]
_):[[Expr]]
_) | Expr -> TypeRep
typ Expr
e' forall a. Eq a => a -> a -> Bool
== Expr -> TypeRep
typ Expr
e -> [[Expr]]
etiers
[[Expr]]
_ -> [[[Expr]]] -> [[Expr]]
tf [[[Expr]]]
etc