{-# LANGUAGE CPP, RecordWildCards, TupleSections #-}
module Conjure.Engine
( conjure
, conjureWithMaxSize
, Args(..)
, args
, conjureWith
, conjureFromSpec
, conjureFromSpecWith
, conjure0
, conjure0With
, Results(..)
, conjpure
, conjpureWith
, conjpureFromSpec
, conjpureFromSpecWith
, conjpure0
, conjpure0With
, candidateExprs
, candidateDefns
, candidateDefns1
, candidateDefnsC
, conjureTheory
, conjureTheoryWith
, module Data.Express
, module Data.Express.Fixtures
, module Conjure.Reason
)
where
import Control.Monad (when)
import Data.Express
import Data.Express.Fixtures hiding ((-==-))
import Test.LeanCheck
import Test.LeanCheck.Tiers
import Test.LeanCheck.Error (errorToFalse)
import Conjure.Expr
import Conjure.Conjurable
import Conjure.Prim
import Conjure.Defn
import Conjure.Defn.Redundancy
import Conjure.Defn.Test
import Conjure.Red
import Conjure.Reason
import System.CPUTime (getCPUTime)
conjure :: Conjurable f => String -> f -> [Prim] -> IO ()
conjure :: forall f. Conjurable f => String -> f -> [Prim] -> IO ()
conjure = Args -> String -> f -> [Prim] -> IO ()
forall f. Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureWith Args
args
conjureFromSpec :: Conjurable f => String -> (f -> Bool) -> [Prim] -> IO ()
conjureFromSpec :: forall f. Conjurable f => String -> (f -> Bool) -> [Prim] -> IO ()
conjureFromSpec = Args -> String -> (f -> Bool) -> [Prim] -> IO ()
forall f.
Conjurable f =>
Args -> String -> (f -> Bool) -> [Prim] -> IO ()
conjureFromSpecWith Args
args
conjure0 :: Conjurable f => String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0 :: forall f.
Conjurable f =>
String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0 = Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0With Args
args
conjureWithMaxSize :: Conjurable f => Int -> String -> f -> [Prim] -> IO ()
conjureWithMaxSize :: forall f. Conjurable f => Int -> String -> f -> [Prim] -> IO ()
conjureWithMaxSize Int
sz = Args -> String -> f -> [Prim] -> IO ()
forall f. Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureWith Args
args
{ maxSize = sz
, maxEquationSize = min sz (maxEquationSize args)
}
data Args = Args
{ Args -> Int
maxTests :: Int
, Args -> Int
maxSize :: Int
, Args -> Int
target :: Int
, Args -> Int
maxEvalRecursions :: Int
, Args -> Int
maxEquationSize :: Int
, Args -> Int
maxSearchTests :: Int
, Args -> Int
maxDeconstructionSize :: Int
, Args -> Int
maxConstantSize :: Int
, Args -> Int
maxPatternSize :: Int
, Args -> Bool
carryOn :: Bool
, Args -> Bool
showTheory :: Bool
, Args -> Bool
usePatterns :: Bool
, Args -> Bool
showRuntime :: Bool
, Args -> Bool
showCandidates :: Bool
, Args -> Bool
showTests :: Bool
, Args -> Bool
showPatterns :: Bool
, Args -> Bool
showDeconstructions :: Bool
, Args -> Bool
rewriting :: Bool
, Args -> Bool
requireDescent :: Bool
, Args -> Bool
adHocRedundancy :: Bool
, Args -> Bool
copyBindings :: Bool
, Args -> Bool
earlyTests :: Bool
, Args -> Bool
atomicNumbers :: Bool
, Args -> Bool
requireZero :: Bool
, Args -> Bool
uniqueCandidates :: Bool
}
args :: Args
args :: Args
args = Args
{ maxTests :: Int
maxTests = Int
360
, maxSize :: Int
maxSize = Int
24
, target :: Int
target = Int
10080
, maxEvalRecursions :: Int
maxEvalRecursions = Int
60
, maxEquationSize :: Int
maxEquationSize = Int
5
, maxSearchTests :: Int
maxSearchTests = Int
100000
, maxDeconstructionSize :: Int
maxDeconstructionSize = Int
4
, maxConstantSize :: Int
maxConstantSize = Int
0
, maxPatternSize :: Int
maxPatternSize = Int
0
, carryOn :: Bool
carryOn = Bool
False
, showTheory :: Bool
showTheory = Bool
False
, usePatterns :: Bool
usePatterns = Bool
True
, showRuntime :: Bool
showRuntime = Bool
True
, showCandidates :: Bool
showCandidates = Bool
False
, showTests :: Bool
showTests = Bool
False
, showDeconstructions :: Bool
showDeconstructions = Bool
False
, showPatterns :: Bool
showPatterns = Bool
False
, rewriting :: Bool
rewriting = Bool
True
, requireDescent :: Bool
requireDescent = Bool
True
, adHocRedundancy :: Bool
adHocRedundancy = Bool
True
, copyBindings :: Bool
copyBindings = Bool
True
, earlyTests :: Bool
earlyTests = Bool
True
, atomicNumbers :: Bool
atomicNumbers = Bool
True
, requireZero :: Bool
requireZero = Bool
False
, uniqueCandidates :: Bool
uniqueCandidates = Bool
False
}
conjureWith :: Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureWith :: forall f. Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureWith Args
args String
nm f
f = Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0With Args
args String
nm f
f (Bool -> f -> Bool
forall a b. a -> b -> a
const Bool
True)
conjureFromSpecWith :: Conjurable f => Args -> String -> (f -> Bool) -> [Prim] -> IO ()
conjureFromSpecWith :: forall f.
Conjurable f =>
Args -> String -> (f -> Bool) -> [Prim] -> IO ()
conjureFromSpecWith Args
args String
nm f -> Bool
p = Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0With Args
args String
nm f
forall a. HasCallStack => a
undefined f -> Bool
p
conjure0With :: Conjurable f => Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0With :: forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> IO ()
conjure0With Args
args String
nm f
f f -> Bool
p [Prim]
es = do
Integer
t0 <- if Args -> Bool
showRuntime Args
args
then IO Integer
getCPUTime
else Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (-Integer
1)
Expr -> IO ()
forall a. Show a => a -> IO ()
print (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)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when ([Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Bndn]
ts Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
Integer -> String -> IO ()
putWithTimeSince Integer
t0 (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"testing " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show ([Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Bndn]
ts) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" combinations of argument values"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
showTests Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"{-"
String -> IO ()
putStr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [Bndn] -> String
showDefn [Bndn]
ts
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-}"
Integer -> String -> IO ()
putWithTimeSince Integer
t0 (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"pruning with " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
nRules String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"/" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
nREs String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" rules"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
showTheory Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"{-"
Thy -> IO ()
printThy Thy
thy
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-}"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> ([Bndn] -> Bool) -> [Bndn] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Bndn] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([Bndn] -> Bool) -> [Bndn] -> Bool
forall a b. (a -> b) -> a -> b
$ Thy -> [Bndn]
invalid Thy
thy) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-- reasoning produced "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show ([Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Thy -> [Bndn]
invalid Thy
thy)) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" incorrect properties,"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" please re-run with more tests for faster results"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
showTheory Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"{-"
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"invalid:"
String -> IO ()
putStr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Bndn -> String) -> [Bndn] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Bndn -> String
showEq ([Bndn] -> [String]) -> [Bndn] -> [String]
forall a b. (a -> b) -> a -> b
$ Thy -> [Bndn]
invalid Thy
thy
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-}"
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
showPatterns Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines
([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Integer -> [String] -> String)
-> [Integer] -> [[String]] -> [String]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Integer
i -> ((String
"-- allowed patterns of size " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
forall a. Show a => a -> String
show Integer
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n{-\n") String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-}") (String -> String) -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines) [Integer
1..]
([[String]] -> [String]) -> [[String]] -> [String]
forall a b. (a -> b) -> a -> b
$ ([Bndn] -> String) -> [[[Bndn]]] -> [[String]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT [Bndn] -> String
showDefn
([[[Bndn]]] -> [[String]]) -> [[[Bndn]]] -> [[String]]
forall a b. (a -> b) -> a -> b
$ Results -> [[[Bndn]]]
patternss Results
results
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
showDeconstructions Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"{- List of allowed deconstructions:"
String -> IO ()
putStr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (Expr -> String) -> [Expr] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Expr -> String
forall a. Show a => a -> String
show ([Expr] -> [String]) -> [Expr] -> [String]
forall a b. (a -> b) -> a -> b
$ Results -> [Expr]
deconstructions Results
results
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-}"
Integer -> Int -> Int -> [([[Bndn]], [[Bndn]])] -> IO ()
pr Integer
t0 Int
1 Int
0 [([[Bndn]], [[Bndn]])]
rs
where
showEq :: Bndn -> String
showEq Bndn
eq = Expr -> String
showExpr (Bndn -> Expr
forall a b. (a, b) -> a
fst Bndn
eq) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" == " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Expr -> String
showExpr (Bndn -> Expr
forall a b. (a, b) -> b
snd Bndn
eq)
pr :: Integer -> Int -> Int -> [([Defn], [Defn])] -> IO ()
pr :: Integer -> Int -> Int -> [([[Bndn]], [[Bndn]])] -> IO ()
pr Integer
t0 Int
n Int
t [] = do Integer -> String -> IO ()
putWithTimeSince Integer
t0 (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"tested " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
t String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" candidates"
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"cannot conjure\n"
pr Integer
t0 Int
n Int
t (([[Bndn]]
is,[[Bndn]]
cs):[([[Bndn]], [[Bndn]])]
rs) = do
let nc :: Int
nc = [[Bndn]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Bndn]]
cs
Integer -> String -> IO ()
putWithTimeSince Integer
t0 (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
nc String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" candidates of size " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
n
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
showCandidates Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
String -> IO ()
putStr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String
"{-"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ([Bndn] -> String) -> [[Bndn]] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map [Bndn] -> String
showDefn [[Bndn]]
cs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String
"-}"]
case [[Bndn]]
is of
[] -> Integer -> Int -> Int -> [([[Bndn]], [[Bndn]])] -> IO ()
pr Integer
t0 (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
tInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
nc) [([[Bndn]], [[Bndn]])]
rs
([Bndn]
_:[[Bndn]]
_) -> do Int -> [[Bndn]] -> [[Bndn]] -> IO ()
pr1 Int
t [[Bndn]]
is [[Bndn]]
cs
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
carryOn Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Integer -> Int -> Int -> [([[Bndn]], [[Bndn]])] -> IO ()
pr Integer
t0 (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
tInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
nc) [([[Bndn]], [[Bndn]])]
rs
where
pr1 :: Int -> [[Bndn]] -> [[Bndn]] -> IO ()
pr1 Int
t [] [[Bndn]]
cs = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
pr1 Int
t ([Bndn]
i:[[Bndn]]
is) [[Bndn]]
cs = do
let ([[Bndn]]
cs',[[Bndn]]
cs'') = ([Bndn] -> Bool) -> [[Bndn]] -> ([[Bndn]], [[Bndn]])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break ([Bndn]
i[Bndn] -> [Bndn] -> Bool
forall a. Eq a => a -> a -> Bool
==) [[Bndn]]
cs
let t' :: Int
t' = Int
t Int -> Int -> Int
forall a. Num a => a -> a -> a
+ [[Bndn]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Bndn]]
cs' Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
Integer -> String -> IO ()
putWithTimeSince Integer
t0 (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"tested " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
t' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" candidates"
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ [Bndn] -> String
showDefn [Bndn]
i
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Args -> Bool
carryOn Args
args) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> [[Bndn]] -> [[Bndn]] -> IO ()
pr1 Int
t' [[Bndn]]
is (Int -> [[Bndn]] -> [[Bndn]]
forall a. Int -> [a] -> [a]
drop Int
1 [[Bndn]]
cs'')
rs :: [([[Bndn]], [[Bndn]])]
rs = [[[Bndn]]] -> [[[Bndn]]] -> [([[Bndn]], [[Bndn]])]
forall a b. [a] -> [b] -> [(a, b)]
zip [[[Bndn]]]
iss [[[Bndn]]]
css
results :: Results
results = Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0With Args
args String
nm f
f f -> Bool
p [Prim]
es
iss :: [[[Bndn]]]
iss = Results -> [[[Bndn]]]
implementationss Results
results
css :: [[[Bndn]]]
css = Results -> [[[Bndn]]]
candidatess Results
results
ts :: [Bndn]
ts = Results -> [Bndn]
bindings Results
results
thy :: Thy
thy = Results -> Thy
theory Results
results
nRules :: Int
nRules = [Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Thy -> [Bndn]
rules Thy
thy)
nREs :: Int
nREs = [Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Thy -> [Bndn]
equations Thy
thy) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
nRules
data Results = Results
{ Results -> [[[Bndn]]]
implementationss :: [[Defn]]
, Results -> [[[Bndn]]]
candidatess :: [[Defn]]
, Results -> [Bndn]
bindings :: Defn
, Results -> Thy
theory :: Thy
, Results -> [[[Bndn]]]
patternss :: [[Defn]]
, Results -> [Expr]
deconstructions :: [Expr]
}
conjpure :: Conjurable f => String -> f -> [Prim] -> Results
conjpure :: forall f. Conjurable f => String -> f -> [Prim] -> Results
conjpure = Args -> String -> f -> [Prim] -> Results
forall f. Conjurable f => Args -> String -> f -> [Prim] -> Results
conjpureWith Args
args
conjpureFromSpec :: Conjurable f => String -> (f -> Bool) -> [Prim] -> Results
conjpureFromSpec :: forall f.
Conjurable f =>
String -> (f -> Bool) -> [Prim] -> Results
conjpureFromSpec = Args -> String -> (f -> Bool) -> [Prim] -> Results
forall f.
Conjurable f =>
Args -> String -> (f -> Bool) -> [Prim] -> Results
conjpureFromSpecWith Args
args
conjpure0 :: Conjurable f => String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0 :: forall f.
Conjurable f =>
String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0 = Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0With Args
args
conjpureWith :: Conjurable f => Args -> String -> f -> [Prim] -> Results
conjpureWith :: forall f. Conjurable f => Args -> String -> f -> [Prim] -> Results
conjpureWith Args
args String
nm f
f = Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0With Args
args String
nm f
f (Bool -> f -> Bool
forall a b. a -> b -> a
const Bool
True)
conjpureFromSpecWith :: Conjurable f => Args -> String -> (f -> Bool) -> [Prim] -> Results
conjpureFromSpecWith :: forall f.
Conjurable f =>
Args -> String -> (f -> Bool) -> [Prim] -> Results
conjpureFromSpecWith Args
args String
nm f -> Bool
p = Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0With Args
args String
nm f
forall a. HasCallStack => a
undefined f -> Bool
p
conjpure0With :: Conjurable f => Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0With :: forall f.
Conjurable f =>
Args -> String -> f -> (f -> Bool) -> [Prim] -> Results
conjpure0With args :: Args
args@(Args{Bool
Int
maxSize :: Args -> Int
maxEquationSize :: Args -> Int
maxTests :: Args -> Int
target :: Args -> Int
maxEvalRecursions :: Args -> Int
maxSearchTests :: Args -> Int
maxDeconstructionSize :: Args -> Int
maxConstantSize :: Args -> Int
maxPatternSize :: Args -> Int
carryOn :: Args -> Bool
showTheory :: Args -> Bool
usePatterns :: Args -> Bool
showRuntime :: Args -> Bool
showCandidates :: Args -> Bool
showTests :: Args -> Bool
showPatterns :: Args -> Bool
showDeconstructions :: Args -> Bool
rewriting :: Args -> Bool
requireDescent :: Args -> Bool
adHocRedundancy :: Args -> Bool
copyBindings :: Args -> Bool
earlyTests :: Args -> Bool
atomicNumbers :: Args -> Bool
requireZero :: Args -> Bool
uniqueCandidates :: Args -> Bool
maxTests :: Int
maxSize :: Int
target :: Int
maxEvalRecursions :: Int
maxEquationSize :: Int
maxSearchTests :: Int
maxDeconstructionSize :: Int
maxConstantSize :: Int
maxPatternSize :: Int
carryOn :: Bool
showTheory :: Bool
usePatterns :: Bool
showRuntime :: Bool
showCandidates :: Bool
showTests :: Bool
showPatterns :: Bool
showDeconstructions :: Bool
rewriting :: Bool
requireDescent :: Bool
adHocRedundancy :: Bool
copyBindings :: Bool
earlyTests :: Bool
atomicNumbers :: Bool
requireZero :: Bool
uniqueCandidates :: Bool
..}) String
nm f
f f -> Bool
p [Prim]
es = Results
{ implementationss :: [[[Bndn]]]
implementationss = [[[Bndn]]]
implementationsT
, candidatess :: [[[Bndn]]]
candidatess = [[[Bndn]]]
candidatesT
, bindings :: [Bndn]
bindings = [Bndn]
tests
, theory :: Thy
theory = Thy
thy
, patternss :: [[[Bndn]]]
patternss = [[[Bndn]]]
patternss
, deconstructions :: [Expr]
deconstructions = [Expr]
deconstructions
}
where
implementationsT :: [[[Bndn]]]
implementationsT = ([Bndn] -> Bool) -> [[[Bndn]]] -> [[[Bndn]]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT [Bndn] -> Bool
implements [[[Bndn]]]
candidatesT
implements :: [Bndn] -> Bool
implements [Bndn]
fx = [Bndn] -> Bool
defnApparentlyTerminates [Bndn]
fx
Bool -> Bool -> Bool
&& [Bndn] -> Bool
test [Bndn]
fx
Bool -> Bool -> Bool
&& Bool -> Bool
errorToFalse (f -> Bool
p (Int -> [Bndn] -> f
forall f. Conjurable f => Int -> [Bndn] -> f
cevl Int
maxEvalRecursions [Bndn]
fx))
candidatesT :: [[[Bndn]]]
candidatesT = (if Bool
uniqueCandidates then Args -> String -> f -> [[[Bndn]]] -> [[[Bndn]]]
forall f.
Conjurable f =>
Args -> String -> f -> [[[Bndn]]] -> [[[Bndn]]]
nubCandidates Args
args String
nm f
f else [[[Bndn]]] -> [[[Bndn]]]
forall a. a -> a
id)
([[[Bndn]]] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> b) -> a -> b
$ (if Int
target Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int -> [[[Bndn]]] -> [[[Bndn]]]
forall a. Int -> [[a]] -> [[a]]
targetiers Int
target else [[[Bndn]]] -> [[[Bndn]]]
forall a. a -> a
id)
([[[Bndn]]] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> b) -> a -> b
$ (if Int
maxSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then Int -> [[[Bndn]]] -> [[[Bndn]]]
forall a. Int -> [a] -> [a]
take Int
maxSize else [[[Bndn]]] -> [[[Bndn]]]
forall a. a -> a
id)
([[[Bndn]]] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> b) -> a -> b
$ [[[Bndn]]]
candidatesTT
([[[Bndn]]]
candidatesTT, Thy
thy, [[[Bndn]]]
patternss, [Expr]
deconstructions) = Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefns Args
args String
nm f
f [Prim]
es
test :: [Bndn] -> Bool
test [Bndn]
dfn = (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
. (Expr -> Expr) -> Int -> [Bndn] -> Bool -> Expr -> Bool
forall a.
Typeable a =>
(Expr -> Expr) -> Int -> [Bndn] -> a -> Expr -> a
deval (f -> Expr -> Expr
forall a. Conjurable a => a -> Expr -> Expr
conjureExpress f
f) Int
maxEvalRecursions [Bndn]
dfn Bool
False)
([Expr] -> Bool) -> [Expr] -> Bool
forall a b. (a -> b) -> a -> b
$ [Expr -> Expr
funToVar Expr
lhs Expr -> Expr -> Expr
-==- Expr
rhs | (Expr
lhs, Expr
rhs) <- [Bndn]
tests]
tests :: [Bndn]
tests = Int -> Int -> String -> f -> [Bndn]
forall f. Conjurable f => Int -> Int -> String -> f -> [Bndn]
conjureTestDefn Int
maxTests Int
maxSearchTests String
nm f
f
-==- :: Expr -> Expr -> Expr
(-==-) = f -> Expr -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation f
f
conjureTheory :: Conjurable f => String -> f -> [Prim] -> IO ()
conjureTheory :: forall f. Conjurable f => String -> f -> [Prim] -> IO ()
conjureTheory = Args -> String -> f -> [Prim] -> IO ()
forall f. Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureTheoryWith Args
args
conjureTheoryWith :: Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureTheoryWith :: forall f. Conjurable f => Args -> String -> f -> [Prim] -> IO ()
conjureTheoryWith Args
args String
nm f
f [Prim]
es = do
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"theory with " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> ([Bndn] -> Int) -> [Bndn] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Bndn] -> String) -> [Bndn] -> String
forall a b. (a -> b) -> a -> b
$ Thy -> [Bndn]
rules Thy
thy) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" rules and "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> ([Bndn] -> Int) -> [Bndn] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Bndn] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Bndn] -> String) -> [Bndn] -> String
forall a b. (a -> b) -> a -> b
$ Thy -> [Bndn]
equations Thy
thy) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" equations"
Thy -> IO ()
printThy Thy
thy
where
Results {theory :: Results -> Thy
theory = Thy
thy} = Args -> String -> f -> [Prim] -> Results
forall f. Conjurable f => Args -> String -> f -> [Prim] -> Results
conjpureWith Args
args String
nm f
f [Prim]
es
candidateDefns :: Conjurable f => Args -> String -> f -> [Prim] -> ([[Defn]], Thy, [[Defn]], [Expr])
candidateDefns :: forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefns Args
args = Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefns' Args
args
where
candidateDefns' :: Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefns' = if Args -> Bool
usePatterns Args
args
then Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefnsC
else Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefns1
candidateDefns1 :: Conjurable f => Args -> String -> f -> [Prim] -> ([[Defn]], Thy, [[Defn]], [Expr])
candidateDefns1 :: forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefns1 Args
args String
nm f
f [Prim]
ps = ([[Expr]] -> [[[Bndn]]])
-> ([[Expr]], Thy, [[[Bndn]]], [Expr])
-> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
forall {t} {a} {b} {c} {d}.
(t -> a) -> (t, b, c, d) -> (a, b, c, d)
first4 ((Expr -> [Bndn]) -> [[Expr]] -> [[[Bndn]]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT Expr -> [Bndn]
forall {b}. b -> [(Expr, b)]
toDefn) (([[Expr]], Thy, [[[Bndn]]], [Expr])
-> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr]))
-> ([[Expr]], Thy, [[[Bndn]]], [Expr])
-> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
forall a b. (a -> b) -> a -> b
$ Args
-> String -> f -> [Prim] -> ([[Expr]], Thy, [[[Bndn]]], [Expr])
forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[Expr]], Thy, [[[Bndn]]], [Expr])
candidateExprs Args
args String
nm f
f [Prim]
ps
where
efxs :: Expr
efxs = String -> f -> Expr
forall f. Conjurable f => String -> f -> Expr
conjureVarApplication String
nm f
f
toDefn :: b -> [(Expr, b)]
toDefn b
e = [(Expr
efxs, b
e)]
first4 :: (t -> a) -> (t, b, c, d) -> (a, b, c, d)
first4 t -> a
f (t
x,b
y,c
z,d
w) = (t -> a
f t
x, b
y, c
z, d
w)
candidateExprs :: Conjurable f => Args -> String -> f -> [Prim] -> ([[Expr]], Thy, [[Defn]], [Expr])
candidateExprs :: forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[Expr]], Thy, [[[Bndn]]], [Expr])
candidateExprs Args{Bool
Int
maxSize :: Args -> Int
maxEquationSize :: Args -> Int
maxTests :: Args -> Int
target :: Args -> Int
maxEvalRecursions :: Args -> Int
maxSearchTests :: Args -> Int
maxDeconstructionSize :: Args -> Int
maxConstantSize :: Args -> Int
maxPatternSize :: Args -> Int
carryOn :: Args -> Bool
showTheory :: Args -> Bool
usePatterns :: Args -> Bool
showRuntime :: Args -> Bool
showCandidates :: Args -> Bool
showTests :: Args -> Bool
showPatterns :: Args -> Bool
showDeconstructions :: Args -> Bool
rewriting :: Args -> Bool
requireDescent :: Args -> Bool
adHocRedundancy :: Args -> Bool
copyBindings :: Args -> Bool
earlyTests :: Args -> Bool
atomicNumbers :: Args -> Bool
requireZero :: Args -> Bool
uniqueCandidates :: Args -> Bool
maxTests :: Int
maxSize :: Int
target :: Int
maxEvalRecursions :: Int
maxEquationSize :: Int
maxSearchTests :: Int
maxDeconstructionSize :: Int
maxConstantSize :: Int
maxPatternSize :: Int
carryOn :: Bool
showTheory :: Bool
usePatterns :: Bool
showRuntime :: Bool
showCandidates :: Bool
showTests :: Bool
showPatterns :: Bool
showDeconstructions :: Bool
rewriting :: Bool
requireDescent :: Bool
adHocRedundancy :: Bool
copyBindings :: Bool
earlyTests :: Bool
atomicNumbers :: Bool
requireZero :: Bool
uniqueCandidates :: Bool
..} String
nm f
f [Prim]
ps =
( [[Expr]]
as [[Expr]] -> [[Expr]] -> [[Expr]]
forall a. [[a]] -> [[a]] -> [[a]]
\/ (Expr -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> [[b]]) -> [[a]] -> [[b]]
concatMapT (Expr -> [[Expr]] -> [[Expr]]
`enumerateFillings` [[Expr]]
recs) [[Expr]]
ts
, Thy
thy
, [[ [(Expr
efxs, Expr
eh)] ]]
, [Expr]
deconstructions
)
where
es :: [Expr]
es = (Prim -> Expr) -> [Prim] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map Prim -> Expr
forall a b. (a, b) -> a
fst [Prim]
ps
ts :: [[Expr]]
ts | Expr -> TypeRep
typ Expr
efxs TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
== TypeRep
boolTy = Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts Expr
andE [[[Expr]]
cs, [[Expr]]
rs]
[[Expr]] -> [[Expr]] -> [[Expr]]
forall a. [[a]] -> [[a]] -> [[a]]
\/ Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts Expr
orE [[[Expr]]
cs, [[Expr]]
rs]
| Bool
otherwise = (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT Expr -> Bool
keepIf
([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts (f -> Expr
forall a. Conjurable a => a -> Expr
conjureIf f
f) [[[Expr]]
cs, [[Expr]]
as, [[Expr]]
rs]
[[Expr]] -> [[Expr]] -> [[Expr]]
forall a. [[a]] -> [[a]] -> [[a]]
\/ Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts (f -> Expr
forall a. Conjurable a => a -> Expr
conjureIf f
f) [[[Expr]]
cs, [[Expr]]
rs, [[Expr]]
as]
cs :: [[Expr]]
cs = (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT (Expr -> [Expr] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [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])
([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ Expr -> [[Expr]]
forN (Bool -> Expr
forall a. Typeable a => a -> Expr
hole (Bool
forall a. HasCallStack => a
undefined :: Bool))
as :: [[Expr]]
as = Expr -> [[Expr]]
forN Expr
efxs
rs :: [[Expr]]
rs = Expr -> [[Expr]]
forR Expr
efxs
forN :: Expr -> [[Expr]]
forN Expr
h = Expr -> (Expr -> Bool) -> [Expr] -> [[Expr]]
enumerateAppsFor Expr
h Expr -> Bool
keep ([Expr] -> [[Expr]]) -> [Expr] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ [Expr]
exs [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr]
es
forR :: Expr -> [[Expr]]
forR Expr
h = (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT (\Expr
e -> (Expr
eh Expr -> [Expr] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem`) (Expr -> [Expr]
holes Expr
e))
([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ Expr -> (Expr -> Bool) -> [Expr] -> [[Expr]]
enumerateAppsFor Expr
h Expr -> Bool
keep ([Expr] -> [[Expr]]) -> [Expr] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ [Expr]
exs [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr]
es [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr
eh]
eh :: Expr
eh = Expr -> Expr
holeAsTypeOf Expr
efxs
efxs :: Expr
efxs = String -> f -> Expr
forall f. Conjurable f => String -> f -> Expr
conjureVarApplication String
nm f
f
(Expr
ef:[Expr]
exs) = Expr -> [Expr]
unfoldApp Expr
efxs
keep :: Expr -> Bool
keep | Bool
rewriting = Thy -> Expr -> Bool
isRootNormalC Thy
thy (Expr -> Bool) -> (Expr -> Expr) -> Expr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Expr
fastMostGeneralVariation
| Bool
otherwise = Bool -> Expr -> Bool
forall a b. a -> b -> a
const Bool
True
keepR :: Expr -> Bool
keepR | Bool
requireDescent = (Expr -> Expr -> Bool) -> Expr -> Expr -> Bool
descends Expr -> Expr -> Bool
isDecOf Expr
efxs
| Bool
otherwise = Bool -> Expr -> Bool
forall a b. a -> b -> a
const Bool
True
where
Expr
e isDecOf :: Expr -> Expr -> Bool
`isDecOf` Expr
e' = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [()] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null
[ ()
| Expr
d <- [Expr]
deconstructions
, [Bndn]
m <- Maybe [Bndn] -> [[Bndn]]
forall a. Maybe a -> [a]
maybeToList (Expr
e Expr -> Expr -> Maybe [Bndn]
`match` Expr
d)
, (Bndn -> Bool) -> [Bndn] -> [Bndn]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Expr -> Expr -> Bool) -> Bndn -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Expr -> Expr -> Bool
forall a. Eq a => a -> a -> Bool
(/=)) [Bndn]
m [Bndn] -> [Bndn] -> Bool
forall a. Eq a => a -> a -> Bool
== [(Expr -> Expr
holeAsTypeOf Expr
e', Expr
e')]
]
deconstructions :: [Expr]
deconstructions :: [Expr]
deconstructions = (Expr -> Bool) -> [Expr] -> [Expr]
forall a. (a -> Bool) -> [a] -> [a]
filter (f -> Int -> Expr -> Bool
forall f. Conjurable f => f -> Int -> Expr -> Bool
conjureIsDeconstruction f
f Int
maxTests)
([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]
candidateDeconstructionsFrom
([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ [[Expr]] -> [Expr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Expr]] -> [Expr])
-> ([[Expr]] -> [[Expr]]) -> [[Expr]] -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [[Expr]] -> [[Expr]]
forall a. Int -> [a] -> [a]
take Int
maxDeconstructionSize
([[Expr]] -> [Expr]) -> [[Expr]] -> [Expr]
forall a b. (a -> b) -> a -> b
$ (Expr -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> [[b]]) -> [[a]] -> [[b]]
concatMapT Expr -> [[Expr]]
forN [[Expr]
hs]
where
hs :: [Expr]
hs = [Expr] -> [Expr]
forall a. Eq a => [a] -> [a]
nub ([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ f -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles f
f
recs :: [[Expr]]
recs = (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT Expr -> Bool
keepR
([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts Expr
ef [Expr -> [[Expr]]
forN Expr
h | Expr
h <- f -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles f
f]
thy :: Thy
thy = (Expr -> Expr -> Bool) -> Thy -> Thy
doubleCheck Expr -> Expr -> Bool
(===)
(Thy -> Thy) -> ([Expr] -> Thy) -> [Expr] -> Thy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Expr -> Bool) -> Int -> [[Expr]] -> Thy
theoryFromAtoms Expr -> Expr -> Bool
(===) Int
maxEquationSize ([[Expr]] -> Thy) -> ([Expr] -> [[Expr]]) -> [Expr] -> Thy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Expr] -> [[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]
forall a. Eq a => [a] -> [a]
nub
([Expr] -> Thy) -> [Expr] -> Thy
forall a b. (a -> b) -> a -> b
$ [Prim] -> [Expr]
cjHoles (String -> f -> Prim
forall a. Conjurable a => String -> a -> Prim
prim String
nm f
fPrim -> [Prim] -> [Prim]
forall a. a -> [a] -> [a]
:[Prim]
ps) [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [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] [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr]
es
=== :: Expr -> Expr -> Bool
(===) = [Prim] -> Int -> Expr -> Expr -> Bool
cjAreEqual (String -> f -> Prim
forall a. Conjurable a => String -> a -> Prim
prim String
nm f
fPrim -> [Prim] -> [Prim]
forall a. a -> [a] -> [a]
:[Prim]
ps) Int
maxTests
candidateDefnsC :: Conjurable f => Args -> String -> f -> [Prim] -> ([[Defn]], Thy, [[Defn]], [Expr])
candidateDefnsC :: forall f.
Conjurable f =>
Args
-> String -> f -> [Prim] -> ([[[Bndn]]], Thy, [[[Bndn]]], [Expr])
candidateDefnsC Args{Bool
Int
maxSize :: Args -> Int
maxEquationSize :: Args -> Int
maxTests :: Args -> Int
target :: Args -> Int
maxEvalRecursions :: Args -> Int
maxSearchTests :: Args -> Int
maxDeconstructionSize :: Args -> Int
maxConstantSize :: Args -> Int
maxPatternSize :: Args -> Int
carryOn :: Args -> Bool
showTheory :: Args -> Bool
usePatterns :: Args -> Bool
showRuntime :: Args -> Bool
showCandidates :: Args -> Bool
showTests :: Args -> Bool
showPatterns :: Args -> Bool
showDeconstructions :: Args -> Bool
rewriting :: Args -> Bool
requireDescent :: Args -> Bool
adHocRedundancy :: Args -> Bool
copyBindings :: Args -> Bool
earlyTests :: Args -> Bool
atomicNumbers :: Args -> Bool
requireZero :: Args -> Bool
uniqueCandidates :: Args -> Bool
maxTests :: Int
maxSize :: Int
target :: Int
maxEvalRecursions :: Int
maxEquationSize :: Int
maxSearchTests :: Int
maxDeconstructionSize :: Int
maxConstantSize :: Int
maxPatternSize :: Int
carryOn :: Bool
showTheory :: Bool
usePatterns :: Bool
showRuntime :: Bool
showCandidates :: Bool
showTests :: Bool
showPatterns :: Bool
showDeconstructions :: Bool
rewriting :: Bool
requireDescent :: Bool
adHocRedundancy :: Bool
copyBindings :: Bool
earlyTests :: Bool
atomicNumbers :: Bool
requireZero :: Bool
uniqueCandidates :: Bool
..} String
nm f
f [Prim]
ps =
( ([Bndn] -> Bool) -> [[[Bndn]]] -> [[[Bndn]]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
discardT [Bndn] -> Bool
hasRedundant ([[[Bndn]]] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> b) -> a -> b
$ ([Bndn] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> [[b]]) -> [[a]] -> [[b]]
concatMapT [Bndn] -> [[[Bndn]]]
fillingsFor [[[Bndn]]]
fss
, Thy
thy
, ([Expr] -> [Bndn]) -> [[[Expr]]] -> [[[Bndn]]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT ((Expr -> Bndn) -> [Expr] -> [Bndn]
forall a b. (a -> b) -> [a] -> [b]
map (,Expr
eh)) [[[Expr]]]
pats
, [Expr]
deconstructions
)
where
pats :: [[[Expr]]]
pats | Int
maxPatternSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Int -> [[[Expr]]] -> [[[Expr]]]
forall a. Int -> [a] -> [a]
take Int
maxPatternSize ([[[Expr]]] -> [[[Expr]]]) -> [[[Expr]]] -> [[[Expr]]]
forall a b. (a -> b) -> a -> b
$ [Expr] -> String -> f -> [[[Expr]]]
forall f. Conjurable f => [Expr] -> String -> f -> [[[Expr]]]
conjurePats [Expr]
es String
nm f
f
| Bool
otherwise = [Expr] -> String -> f -> [[[Expr]]]
forall f. Conjurable f => [Expr] -> String -> f -> [[[Expr]]]
conjurePats [Expr]
es String
nm f
f
fss :: [[[Bndn]]]
fss = ([Expr] -> [[[Bndn]]]) -> [[[Expr]]] -> [[[Bndn]]]
forall a b. (a -> [[b]]) -> [[a]] -> [[b]]
concatMapT [Expr] -> [[[Bndn]]]
ps2fss [[[Expr]]]
pats
es :: [Expr]
es = (Prim -> Expr) -> [Prim] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map Prim -> Expr
forall a b. (a, b) -> a
fst [Prim]
ps
eh :: Expr
eh = Expr -> Expr
holeAsTypeOf Expr
efxs
efxs :: Expr
efxs = String -> f -> Expr
forall f. Conjurable f => String -> f -> Expr
conjureVarApplication String
nm f
f
(Expr
ef:[Expr]
_) = Expr -> [Expr]
unfoldApp Expr
efxs
keep :: Expr -> Bool
keep | Bool
rewriting = Thy -> Expr -> Bool
isRootNormalC Thy
thy (Expr -> Bool) -> (Expr -> Expr) -> Expr -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Expr
fastMostGeneralVariation
| Bool
otherwise = Bool -> Expr -> Bool
forall a b. a -> b -> a
const Bool
True
keepBndn :: Bndn -> Bool
keepBndn | Bool
rewriting = \b :: Bndn
b@(Expr
_,Expr
rhs) -> Bndn -> Bool
isBaseCase Bndn
b Bool -> Bool -> Bool
|| Expr -> Int
size (Thy -> Expr -> Expr
normalize Thy
thy Expr
rhs) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Expr -> Int
size Expr
rhs
| Bool
otherwise = Bool -> Bndn -> Bool
forall a b. a -> b -> a
const Bool
True
appsWith :: Expr -> [Expr] -> [[Expr]]
appsWith :: Expr -> [Expr] -> [[Expr]]
appsWith Expr
eh [Expr]
vs = Expr -> (Expr -> Bool) -> [Expr] -> [[Expr]]
enumerateAppsFor Expr
eh Expr -> Bool
k ([Expr] -> [[Expr]]) -> [Expr] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ [Expr]
vs [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr]
es
where
k :: Expr -> Bool
k | Bool
atomicNumbers Bool -> Bool -> Bool
&& Expr -> Bool
isNumeric Expr
eh = \Expr
e -> Expr -> Bool
keepNumeric Expr
e Bool -> Bool -> Bool
&& Expr -> Bool
keep Expr
e
| Int
maxConstantSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = \Expr
e -> Expr -> Bool
keepConstant Expr
e Bool -> Bool -> Bool
&& Expr -> Bool
keep Expr
e
| Bool
otherwise = Expr -> Bool
keep
keepNumeric :: Expr -> Bool
keepNumeric Expr
e = Expr -> Bool
isFun Expr
e Bool -> Bool -> Bool
|| Expr -> Bool
isConst Expr
e Bool -> Bool -> Bool
|| Bool -> Bool
not (Expr -> Bool
isGround Expr
e)
keepConstant :: Expr -> Bool
keepConstant Expr
e = Expr -> Bool
isFun Expr
e Bool -> Bool -> Bool
|| Expr -> Bool
isConst Expr
e Bool -> Bool -> Bool
|| Bool -> Bool
not (Expr -> Bool
isGround Expr
e) Bool -> Bool -> Bool
|| Expr -> Int
size Expr
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
maxConstantSize
isRedundant :: [Bndn] -> Bool
isRedundant | Bool
adHocRedundancy = \[Bndn]
e -> [Bndn] -> Bool
isRedundantDefn [Bndn]
e Bool -> Bool -> Bool
|| (Expr -> Expr) -> [Bndn] -> Bool
isRedundantModuloRewriting (Thy -> Expr -> Expr
normalize Thy
thy) [Bndn]
e
| Bool
otherwise = Bool -> [Bndn] -> Bool
forall a b. a -> b -> a
const Bool
False
hasRedundant :: [Bndn] -> Bool
hasRedundant | Bool
adHocRedundancy = [Bndn] -> Bool
hasRedundantRecursion
| Bool
otherwise = Bool -> [Bndn] -> Bool
forall a b. a -> b -> a
const Bool
False
isNumeric :: Expr -> Bool
isNumeric = f -> Expr -> Bool
forall f. Conjurable f => f -> Expr -> Bool
conjureIsNumeric f
f
-==- :: Expr -> Expr -> Expr
(-==-) = f -> Expr -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation f
f
tests :: [Bndn]
tests = Int -> Int -> String -> f -> [Bndn]
forall f. Conjurable f => Int -> Int -> String -> f -> [Bndn]
conjureTestDefn Int
maxTests Int
maxSearchTests String
nm f
f
exprExpr :: Expr -> Expr
exprExpr = f -> Expr -> Expr
forall a. Conjurable a => a -> Expr -> Expr
conjureExpress f
f
ps2fss :: [Expr] -> [[Defn]]
ps2fss :: [Expr] -> [[[Bndn]]]
ps2fss [Expr]
pats = ([Bndn] -> Bool) -> [[[Bndn]]] -> [[[Bndn]]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
discardT [Bndn] -> Bool
isRedundant
([[[Bndn]]] -> [[[Bndn]]])
-> ([[[Bndn]]] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Bndn]]] -> [[[Bndn]]]
forall a. [[[a]]] -> [[[a]]]
products
([[[Bndn]]] -> [[[Bndn]]]) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> b) -> a -> b
$ (Expr -> [[Bndn]]) -> [Expr] -> [[[Bndn]]]
forall a b. (a -> b) -> [a] -> [b]
map Expr -> [[Bndn]]
p2eess [Expr]
pats
where
p2eess :: Expr -> [[Bndn]]
p2eess :: Expr -> [[Bndn]]
p2eess Expr
pat | Bool
copyBindings Bool -> Bool -> Bool
&& f -> Expr -> Bool
forall f. Conjurable f => f -> Expr -> Bool
isGroundPat f
f Expr
pat = [[(Expr
pat, f -> Expr -> Expr
forall a. Conjurable a => a -> Expr -> Expr
toValPat f
f Expr
pat)]]
p2eess Expr
pat = (Expr -> Bndn) -> [[Expr]] -> [[Bndn]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (Expr
pat,)
([[Expr]] -> [[Bndn]])
-> ([Expr] -> [[Expr]]) -> [Expr] -> [[Bndn]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT Expr -> Bool
keepBase
([[Expr]] -> [[Expr]])
-> ([Expr] -> [[Expr]]) -> [Expr] -> [[Expr]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr] -> [[Expr]]
appsWith Expr
pat
([Expr] -> [[Expr]]) -> ([Expr] -> [Expr]) -> [Expr] -> [[Expr]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Expr] -> [Expr]
forall a. Int -> [a] -> [a]
drop Int
1
([Expr] -> [[Bndn]]) -> [Expr] -> [[Bndn]]
forall a b. (a -> b) -> a -> b
$ Expr -> [Expr]
vars Expr
pat [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr
eh | (([Expr], Expr) -> Bool) -> [([Expr], Expr)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (([Expr] -> Expr -> Bool) -> ([Expr], Expr) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry [Expr] -> Expr -> Bool
should) ([[Expr]] -> [Expr] -> [([Expr], Expr)]
forall a b. [a] -> [b] -> [(a, b)]
zip [[Expr]]
aess [Expr]
aes)]
where
keepBase :: Expr -> Bool
keepBase
| Bool -> Bool
not Bool
earlyTests = Bool -> Expr -> Bool
forall a b. a -> b -> a
const Bool
True
| (Expr -> Bool) -> [Expr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Expr -> Bool
isVar (Expr -> [Expr]
unfoldApp Expr
pat) = Bool -> Expr -> Bool
forall a b. a -> b -> a
const Bool
True
| Bool
otherwise = \Expr
e -> Expr -> Bool
hasHole Expr
e Bool -> Bool -> Bool
|| Expr -> Bool
reallyKeepBase Expr
e
reallyKeepBase :: Expr -> Bool
reallyKeepBase Expr
e = [Bool] -> Bool
forall (t :: * -> *). Foldable t => t Bool -> Bool
and
[ Bool -> Bool
errorToFalse (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Bool -> Expr -> Bool
forall a. Typeable a => a -> Expr -> a
eval Bool
False (Expr -> Bool) -> Expr -> Bool
forall a b. (a -> b) -> a -> b
$ (Expr
e Expr -> [Bndn] -> Expr
//- [Bndn]
bs) Expr -> Expr -> Expr
-==- Expr
rhs
| (Expr
lhs,Expr
rhs) <- [Bndn]
tests
, Just [Bndn]
bs <- [Expr
lhs Expr -> Expr -> Maybe [Bndn]
`matchArgs` Expr
pat]
]
matchArgs :: Expr -> Expr -> Maybe [Bndn]
matchArgs Expr
efxs Expr
efys = [Expr] -> Expr
fold ((Expr -> Expr) -> [Expr] -> [Expr]
forall a b. (a -> b) -> [a] -> [b]
map Expr -> Expr
exprExpr (Int -> [Expr] -> [Expr]
forall a. Int -> [a] -> [a]
drop Int
1 (Expr -> [Expr]
unfoldApp Expr
efxs)))
Expr -> Expr -> Maybe [Bndn]
`match` [Expr] -> Expr
fold (Int -> [Expr] -> [Expr]
forall a. Int -> [a] -> [a]
drop Int
1 (Expr -> [Expr]
unfoldApp Expr
efys))
should :: [Expr] -> Expr -> Bool
should [Expr]
aes Expr
ae = [Expr] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Expr] -> [Expr]
forall a. Eq a => [a] -> [a]
nub [Expr]
aes) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1 Bool -> Bool -> Bool
&& Expr -> Bool
hasVar Expr
ae Bool -> Bool -> Bool
&& (Expr -> Bool
isApp Expr
ae Bool -> Bool -> Bool
|| Expr -> Bool
isUnbreakable Expr
ae)
Bool -> Bool -> Bool
&& (Bool -> Bool
not Bool
requireZero Bool -> Bool -> Bool
|| Bool -> Bool
not (Expr -> Bool
isNumeric Expr
ae) Bool -> Bool -> Bool
|| (Expr -> Bool) -> [Expr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Expr -> Bool
isZero [Expr]
aes)
aes :: [Expr]
aes = ([Expr] -> [Expr]
forall a. HasCallStack => [a] -> [a]
tail ([Expr] -> [Expr]) -> (Expr -> [Expr]) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
unfoldApp (Expr -> [Expr]) -> (Expr -> Expr) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Expr
rehole) Expr
pat
aess :: [[Expr]]
aess = [[Expr]] -> [[Expr]]
forall a. [[a]] -> [[a]]
transpose ([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ (Expr -> [Expr]) -> [Expr] -> [[Expr]]
forall a b. (a -> b) -> [a] -> [b]
map ([Expr] -> [Expr]
forall a. HasCallStack => [a] -> [a]
tail ([Expr] -> [Expr]) -> (Expr -> [Expr]) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
unfoldApp (Expr -> [Expr]) -> (Expr -> Expr) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> Expr
rehole) [Expr]
pats
fillingsFor1 :: Bndn -> [[Bndn]]
fillingsFor1 :: Bndn -> [[Bndn]]
fillingsFor1 (Expr
ep,Expr
er) = (Bndn -> Bool) -> [[Bndn]] -> [[Bndn]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT Bndn -> Bool
keepBndn
([[Bndn]] -> [[Bndn]])
-> ([[Expr]] -> [[Bndn]]) -> [[Expr]] -> [[Bndn]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Expr] -> Bndn) -> [[[Expr]]] -> [[Bndn]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT (\[Expr]
es -> (Expr
ep,Expr -> [Expr] -> Expr
fill Expr
er [Expr]
es))
([[[Expr]]] -> [[Bndn]])
-> ([[Expr]] -> [[[Expr]]]) -> [[Expr]] -> [[Bndn]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Expr]]] -> [[[Expr]]]
forall a. [[[a]]] -> [[[a]]]
products
([[[Expr]]] -> [[[Expr]]])
-> ([[Expr]] -> [[[Expr]]]) -> [[Expr]] -> [[[Expr]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [[Expr]] -> [[[Expr]]]
forall a. Int -> a -> [a]
replicate ([Expr] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([Expr] -> Int) -> [Expr] -> Int
forall a b. (a -> b) -> a -> b
$ Expr -> [Expr]
holes Expr
er)
([[Expr]] -> [[Bndn]]) -> [[Expr]] -> [[Bndn]]
forall a b. (a -> b) -> a -> b
$ Expr -> [[Expr]]
recs' Expr
ep
fillingsFor :: Defn -> [[Defn]]
fillingsFor :: [Bndn] -> [[[Bndn]]]
fillingsFor = [[[Bndn]]] -> [[[Bndn]]]
forall a. [[[a]]] -> [[[a]]]
products ([[[Bndn]]] -> [[[Bndn]]])
-> ([Bndn] -> [[[Bndn]]]) -> [Bndn] -> [[[Bndn]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Bndn -> [[Bndn]]) -> [Bndn] -> [[[Bndn]]]
forall a b. (a -> b) -> [a] -> [b]
map Bndn -> [[Bndn]]
fillingsFor1
keepR :: Expr -> Expr -> Bool
keepR Expr
ep | Bool
requireDescent = (Expr -> Expr -> Bool) -> Expr -> Expr -> Bool
descends Expr -> Expr -> Bool
isDecOf Expr
ep
| Bool
otherwise = Bool -> Expr -> Bool
forall a b. a -> b -> a
const Bool
True
where
Expr
e isDecOf :: Expr -> Expr -> Bool
`isDecOf` Expr
e' = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [()] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null
[ ()
| Expr
d <- [Expr]
deconstructions
, [Bndn]
m <- Maybe [Bndn] -> [[Bndn]]
forall a. Maybe a -> [a]
maybeToList (Expr
e Expr -> Expr -> Maybe [Bndn]
`match` Expr
d)
, Expr -> [Bndn] -> Maybe Expr
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Expr
h [Bndn]
m Maybe Expr -> Maybe Expr -> Bool
forall a. Eq a => a -> a -> Bool
== Expr -> Maybe Expr
forall a. a -> Maybe a
Just Expr
e'
, (Bndn -> Bool) -> [Bndn] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\(Expr
e1,Expr
e2) -> Expr
e1 Expr -> Expr -> Bool
forall a. Eq a => a -> a -> Bool
== Expr
h Bool -> Bool -> Bool
|| Expr -> Bool
isVar Expr
e2) [Bndn]
m
]
where
h :: Expr
h = Expr -> Expr
holeAsTypeOf Expr
e'
deconstructions :: [Expr]
deconstructions :: [Expr]
deconstructions = (Expr -> Bool) -> [Expr] -> [Expr]
forall a. (a -> Bool) -> [a] -> [a]
filter (f -> Int -> Expr -> Bool
forall f. Conjurable f => f -> Int -> Expr -> Bool
conjureIsDeconstruction f
f Int
maxTests)
([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]
candidateDeconstructionsFromHoled
([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ [[Expr]] -> [Expr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Expr]] -> [Expr])
-> ([[Expr]] -> [[Expr]]) -> [[Expr]] -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [[Expr]] -> [[Expr]]
forall a. Int -> [a] -> [a]
take Int
maxDeconstructionSize
([[Expr]] -> [Expr]) -> [[Expr]] -> [Expr]
forall a b. (a -> b) -> a -> b
$ (Expr -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> [[b]]) -> [[a]] -> [[b]]
concatMapT (Expr -> [Expr] -> [[Expr]]
`appsWith` [Expr]
hs) [[Expr]
hs]
where
hs :: [Expr]
hs = [Expr] -> [Expr]
forall a. Eq a => [a] -> [a]
nub ([Expr] -> [Expr]) -> [Expr] -> [Expr]
forall a b. (a -> b) -> a -> b
$ f -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles f
f
recs :: Expr -> [[Expr]]
recs Expr
ep = (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT (Expr -> Expr -> Bool
keepR Expr
ep)
([[Expr]] -> [[Expr]])
-> ([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
discardT (\Expr
e -> Expr
e Expr -> Expr -> Bool
forall a. Eq a => a -> a -> Bool
== Expr
ep)
([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ [Expr] -> [[Expr]]
recsV' ([Expr] -> [Expr]
forall a. HasCallStack => [a] -> [a]
tail (Expr -> [Expr]
vars Expr
ep))
recsV :: [Expr] -> [[Expr]]
recsV [Expr]
vs = (Expr -> Bool) -> [[Expr]] -> [[Expr]]
forall a. (a -> Bool) -> [[a]] -> [[a]]
filterT (\Expr
e -> (Expr -> Bool) -> [Expr] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Expr -> [Expr] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Expr]
vs) (Expr -> [Expr]
vars Expr
e))
([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts Expr
ef [Expr -> [Expr] -> [[Expr]]
appsWith Expr
h [Expr]
vs | Expr
h <- f -> [Expr]
forall a. Conjurable a => a -> [Expr]
conjureArgumentHoles f
f]
recs' :: Expr -> [[Expr]]
recs' Expr
ep = [[Expr]] -> Maybe [[Expr]] -> [[Expr]]
forall a. a -> Maybe a -> a
fromMaybe [[Expr]]
forall {a}. a
errRP (Maybe [[Expr]] -> [[Expr]]) -> Maybe [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ Expr -> [(Expr, [[Expr]])] -> Maybe [[Expr]]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Expr
ep [(Expr, [[Expr]])]
eprs
where
eprs :: [(Expr, [[Expr]])]
eprs = [(Expr
ep, Expr -> [[Expr]]
recs Expr
ep) | Expr
ep <- [Expr]
possiblePats]
possiblePats :: [Expr]
possiblePats = [Expr] -> [Expr]
forall a. Ord a => [a] -> [a]
nubSort ([Expr] -> [Expr])
-> ([[[Expr]]] -> [Expr]) -> [[[Expr]]] -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Expr]] -> [Expr]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Expr]] -> [Expr])
-> ([[[Expr]]] -> [[Expr]]) -> [[[Expr]]] -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Expr]]] -> [[Expr]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[Expr]]] -> [Expr]) -> [[[Expr]]] -> [Expr]
forall a b. (a -> b) -> a -> b
$ [[[Expr]]]
pats
recsV' :: [Expr] -> [[Expr]]
recsV' [Expr]
vs = [[Expr]] -> Maybe [[Expr]] -> [[Expr]]
forall a. a -> Maybe a -> a
fromMaybe [[Expr]]
forall {a}. a
errRV (Maybe [[Expr]] -> [[Expr]]) -> Maybe [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ [Expr] -> [([Expr], [[Expr]])] -> Maybe [[Expr]]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [Expr]
vs [([Expr], [[Expr]])]
evrs
where
evrs :: [([Expr], [[Expr]])]
evrs = [([Expr]
vs, [Expr] -> [[Expr]]
recsV [Expr]
vs) | [Expr]
vs <- [[Expr]] -> [[Expr]]
forall a. Ord a => [a] -> [a]
nubSort ([[Expr]] -> [[Expr]]) -> [[Expr]] -> [[Expr]]
forall a b. (a -> b) -> a -> b
$ (Expr -> [Expr]) -> [Expr] -> [[Expr]]
forall a b. (a -> b) -> [a] -> [b]
map ([Expr] -> [Expr]
forall a. HasCallStack => [a] -> [a]
tail ([Expr] -> [Expr]) -> (Expr -> [Expr]) -> Expr -> [Expr]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr -> [Expr]
vars) [Expr]
possiblePats]
thy :: Thy
thy = (Expr -> Expr -> Bool) -> Thy -> Thy
doubleCheck Expr -> Expr -> Bool
(===)
(Thy -> Thy) -> ([Expr] -> Thy) -> [Expr] -> Thy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Expr -> Expr -> Bool) -> Int -> [[Expr]] -> Thy
theoryFromAtoms Expr -> Expr -> Bool
(===) Int
maxEquationSize ([[Expr]] -> Thy) -> ([Expr] -> [[Expr]]) -> [Expr] -> Thy
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Expr] -> [[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]
forall a. Eq a => [a] -> [a]
nub
([Expr] -> Thy) -> [Expr] -> Thy
forall a b. (a -> b) -> a -> b
$ [Prim] -> [Expr]
cjHoles (String -> f -> Prim
forall a. Conjurable a => String -> a -> Prim
prim String
nm f
fPrim -> [Prim] -> [Prim]
forall a. a -> [a] -> [a]
:[Prim]
ps) [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [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] [Expr] -> [Expr] -> [Expr]
forall a. [a] -> [a] -> [a]
++ [Expr]
es
=== :: Expr -> Expr -> Bool
(===) = [Prim] -> Int -> Expr -> Expr -> Bool
cjAreEqual (String -> f -> Prim
forall a. Conjurable a => String -> a -> Prim
prim String
nm f
fPrim -> [Prim] -> [Prim]
forall a. a -> [a] -> [a]
:[Prim]
ps) Int
maxTests
isUnbreakable :: Expr -> Bool
isUnbreakable = f -> Expr -> Bool
forall f. Conjurable f => f -> Expr -> Bool
conjureIsUnbreakable f
f
errRP :: a
errRP = String -> a
forall a. HasCallStack => String -> a
error String
"candidateDefnsC: unexpected pattern. You have found a bug, please report it."
errRV :: a
errRV = String -> a
forall a. HasCallStack => String -> a
error String
"candidateDefnsC: unexpected variables. You have found a bug, please report it."
isGroundPat :: Conjurable f => f -> Expr -> Bool
isGroundPat :: forall f. Conjurable f => f -> Expr -> Bool
isGroundPat f
f Expr
pat = 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 -> Bool
forall a b. (a -> b) -> a -> b
$ Expr
gpat Expr -> Expr -> Expr
-==- Expr
gpat
where
gpat :: Expr
gpat = f -> Expr -> Expr
forall a. Conjurable a => a -> Expr -> Expr
toGroundPat f
f Expr
pat
-==- :: Expr -> Expr -> Expr
(-==-) = f -> Expr -> Expr -> Expr
forall f. Conjurable f => f -> Expr -> Expr -> Expr
conjureMkEquation f
f
toGroundPat :: Conjurable f => f -> Expr -> Expr
toGroundPat :: forall a. Conjurable a => a -> Expr -> Expr
toGroundPat f
f Expr
pat = [Expr] -> Expr
foldApp (String -> f -> Expr
forall a. Typeable a => String -> a -> Expr
value String
"f" f
f Expr -> [Expr] -> [Expr]
forall a. a -> [a] -> [a]
: [Expr] -> [Expr]
forall a. HasCallStack => [a] -> [a]
tail (Expr -> [Expr]
unfoldApp Expr
pat))
toValPat :: Conjurable f => f -> Expr -> Expr
toValPat :: forall a. Conjurable a => a -> Expr -> Expr
toValPat f
f = f -> Expr -> Expr
forall a. Conjurable a => a -> Expr -> Expr
conjureExpress f
f (Expr -> Expr) -> (Expr -> Expr) -> Expr -> Expr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. f -> Expr -> Expr
forall a. Conjurable a => a -> Expr -> Expr
toGroundPat f
f
keepIf :: Expr -> Bool
keepIf :: Expr -> Bool
keepIf (Value String
"if" Dynamic
_ :$ Expr
ep :$ Expr
ex :$ Expr
ey)
| Expr
ex Expr -> Expr -> Bool
forall a. Eq a => a -> a -> Bool
== Expr
ey = Bool
False
| Expr -> Bool
anormal Expr
ep = Bool
False
| Bool
otherwise = case Expr -> Maybe Bndn
binding Expr
ep of
Just (Expr
v,Expr
e) -> Expr
v Expr -> [Expr] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` Expr -> [Expr]
values Expr
ex
Maybe Bndn
Nothing -> Bool
True
where
anormal :: Expr -> Bool
anormal (Value String
"==" Dynamic
_ :$ Expr
e1 :$ Expr
e2) | Expr -> Bool
isVar Expr
e2 Bool -> Bool -> Bool
|| Expr -> Bool
isConst Expr
e1 = Bool
True
anormal Expr
_ = Bool
False
binding :: Expr -> Maybe (Expr,Expr)
binding :: Expr -> Maybe Bndn
binding (Value String
"==" Dynamic
_ :$ Expr
e1 :$ Expr
e2) | Expr -> Bool
isVar Expr
e1 = Bndn -> Maybe Bndn
forall a. a -> Maybe a
Just (Expr
e1,Expr
e2)
| Expr -> Bool
isVar Expr
e2 = Bndn -> Maybe Bndn
forall a. a -> Maybe a
Just (Expr
e2,Expr
e1)
binding Expr
_ = Maybe Bndn
forall a. Maybe a
Nothing
keepIf Expr
_ = String -> Bool
forall a. HasCallStack => String -> a
error String
"Conjure.Engine.keepIf: not an if"
nubCandidates :: Conjurable f => Args -> String -> f -> [[Defn]] -> [[Defn]]
nubCandidates :: forall f.
Conjurable f =>
Args -> String -> f -> [[[Bndn]]] -> [[[Bndn]]]
nubCandidates Args{Bool
Int
maxSize :: Args -> Int
maxEquationSize :: Args -> Int
maxTests :: Args -> Int
target :: Args -> Int
maxEvalRecursions :: Args -> Int
maxSearchTests :: Args -> Int
maxDeconstructionSize :: Args -> Int
maxConstantSize :: Args -> Int
maxPatternSize :: Args -> Int
carryOn :: Args -> Bool
showTheory :: Args -> Bool
usePatterns :: Args -> Bool
showRuntime :: Args -> Bool
showCandidates :: Args -> Bool
showTests :: Args -> Bool
showPatterns :: Args -> Bool
showDeconstructions :: Args -> Bool
rewriting :: Args -> Bool
requireDescent :: Args -> Bool
adHocRedundancy :: Args -> Bool
copyBindings :: Args -> Bool
earlyTests :: Args -> Bool
atomicNumbers :: Args -> Bool
requireZero :: Args -> Bool
uniqueCandidates :: Args -> Bool
maxTests :: Int
maxSize :: Int
target :: Int
maxEvalRecursions :: Int
maxEquationSize :: Int
maxSearchTests :: Int
maxDeconstructionSize :: Int
maxConstantSize :: Int
maxPatternSize :: Int
carryOn :: Bool
showTheory :: Bool
usePatterns :: Bool
showRuntime :: Bool
showCandidates :: Bool
showTests :: Bool
showPatterns :: Bool
showDeconstructions :: Bool
rewriting :: Bool
requireDescent :: Bool
adHocRedundancy :: Bool
copyBindings :: Bool
earlyTests :: Bool
atomicNumbers :: Bool
requireZero :: Bool
uniqueCandidates :: Bool
..} String
nm f
f =
([Bndn] -> [Bndn] -> Bool) -> [[[Bndn]]] -> [[[Bndn]]]
forall a. (a -> a -> Bool) -> [[a]] -> [[a]]
discardLaterT (([Bndn] -> [Bndn] -> Bool) -> [[[Bndn]]] -> [[[Bndn]]])
-> ([Bndn] -> [Bndn] -> Bool) -> [[[Bndn]]] -> [[[Bndn]]]
forall a b. (a -> b) -> a -> b
$ Int -> Int -> String -> f -> [Bndn] -> [Bndn] -> Bool
forall f.
Conjurable f =>
Int -> Int -> String -> f -> [Bndn] -> [Bndn] -> Bool
equalModuloTesting Int
maxTests Int
maxEvalRecursions String
nm f
f
productsWith :: ([a] -> a) -> [ [[a]] ] -> [[a]]
productsWith :: forall a. ([a] -> a) -> [[[a]]] -> [[a]]
productsWith [a] -> a
f = ([a] -> a) -> [[[a]]] -> [[a]]
forall a b. (a -> b) -> [[a]] -> [[b]]
mapT [a] -> a
f ([[[a]]] -> [[a]]) -> ([[[a]]] -> [[[a]]]) -> [[[a]]] -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[a]]] -> [[[a]]]
forall a. [[[a]]] -> [[[a]]]
products
delayedProducts :: [ [[a]] ] -> [[ [a] ]]
delayedProducts :: forall a. [[[a]]] -> [[[a]]]
delayedProducts [[[a]]]
xsss = [[[a]]] -> [[[a]]]
forall a. [[[a]]] -> [[[a]]]
products [[[a]]]
xsss [[[a]]] -> Int -> [[[a]]]
forall a. [[a]] -> Int -> [[a]]
`addWeight` ([[[a]]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[a]]]
xsss Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
delayedProductsWith :: ([a] -> a) -> [ [[a]] ] -> [[a]]
delayedProductsWith :: forall a. ([a] -> a) -> [[[a]]] -> [[a]]
delayedProductsWith [a] -> a
f [[[a]]]
xsss = ([a] -> a) -> [[[a]]] -> [[a]]
forall a. ([a] -> a) -> [[[a]]] -> [[a]]
productsWith [a] -> a
f [[[a]]]
xsss [[a]] -> Int -> [[a]]
forall a. [[a]] -> Int -> [[a]]
`addWeight` [[[a]]] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[a]]]
xsss
foldAppProducts :: Expr -> [ [[Expr]] ] -> [[Expr]]
foldAppProducts :: Expr -> [[[Expr]]] -> [[Expr]]
foldAppProducts Expr
ef = ([Expr] -> Expr) -> [[[Expr]]] -> [[Expr]]
forall a. ([a] -> a) -> [[[a]]] -> [[a]]
delayedProductsWith ([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]
:))
showTime :: Integer -> String
showTime :: Integer -> String
showTime Integer
ps = Double -> String
forall a. Show a => a -> String
show Double
s String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"s"
where
s :: Double
s = Integer -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
ds Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
10.0
ds :: Integer
ds = Integer
ps Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
`div` Integer
100000000000
putWithTimeSince :: Integer -> String -> IO ()
putWithTimeSince :: Integer -> String -> IO ()
putWithTimeSince Integer
start String
msg
| Integer
start Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-- " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg
| String
msg String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
msg = do
Integer
end <- IO Integer
getCPUTime
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"-- " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Integer -> String
showTime (Integer
end Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
start) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
", " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
msg
| Bool
otherwise = String -> IO ()
forall a. HasCallStack => String -> a
error String
"putWithTimeSince: the impossible happened (GHC/Compiler/Interpreter bug?!)"
targetiers :: Int -> [[a]] -> [[a]]
targetiers :: forall a. Int -> [[a]] -> [[a]]
targetiers Int
n [[a]]
xss
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = []
| Bool
otherwise = case [[a]]
xss of [] -> []
([a]
xs:[[a]]
xss) -> [a]
xs [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: Int -> [[a]] -> [[a]]
forall a. Int -> [[a]] -> [[a]]
targetiers (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- [a] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs) [[a]]
xss
boolTy :: TypeRep
boolTy :: TypeRep
boolTy = Expr -> TypeRep
typ Expr
b_