{-# LANGUAGE CPP, RecordWildCards, TupleSections #-}
module Conjure.Settings
(
maxTests
, maxSize
, target
, maxRecursions
, maxEquationSize
, maxSearchTests
, maxDeconstructionSize
, maxConstantSize
, maxPatternSize
, maxPatternDepth
, showCandidates
, showTheory
, singlePattern
, showTests
, showPatterns
, showDeconstructions
, carryOn
, dontRewrite
, dontRequireDescent
, omitAssortedPruning
, omitEarlyTests
, dontCopyBindings
, nonAtomicNumbers
, uniqueCandidates
, actual
, maxTestsI
, targetAndMaxSizeI
, maxRecursionsI
, maxEquationSizeI
, maxSearchTestsI
, maxDeconstructionSizeI
, maxConstantSizeI
, maxPatternSizeI
, maxPatternDepthI
, showCandidatesI
, showTheoryI
, singlePatternI
, showTestsI
, showPatternsI
, showDeconstructionsI
, carryOnI
, rewriteI
, requireDescentI
, assortedPruningI
, earlyTestsI
, copyBindingsI
, atomicNumbersI
, uniqueCandidatesI
)
where
import Conjure.Utils
import Data.Express (val, eval, typ)
import Conjure.Ingredient (Ingredient)
data Setting
= Noop
| MaxTests Int
| MaxSize Int
| Target Int
| MaxRecursions Int
| MaxEquationSize Int
| MaxSearchTests Int
| MaxDeconstructionSize Int
| MaxConstantSize Int
| MaxPatternSize Int
| MaxPatternDepth Int
| CarryOn
| ShowTheory
| SinglePattern
| ShowCandidates
| ShowTests
| ShowPatterns
| ShowDeconstructions
| DontRewrite
| DontRequireDescent
| OmitAssortedPruning
| OmitEarlyTests
| DontCopyBindings
| AtomicNumbers
| NonAtomicNumbers
| UniqueCandidates
deriving (Setting -> Setting -> Bool
(Setting -> Setting -> Bool)
-> (Setting -> Setting -> Bool) -> Eq Setting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Setting -> Setting -> Bool
== :: Setting -> Setting -> Bool
$c/= :: Setting -> Setting -> Bool
/= :: Setting -> Setting -> Bool
Eq, Eq Setting
Eq Setting =>
(Setting -> Setting -> Ordering)
-> (Setting -> Setting -> Bool)
-> (Setting -> Setting -> Bool)
-> (Setting -> Setting -> Bool)
-> (Setting -> Setting -> Bool)
-> (Setting -> Setting -> Setting)
-> (Setting -> Setting -> Setting)
-> Ord Setting
Setting -> Setting -> Bool
Setting -> Setting -> Ordering
Setting -> Setting -> Setting
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Setting -> Setting -> Ordering
compare :: Setting -> Setting -> Ordering
$c< :: Setting -> Setting -> Bool
< :: Setting -> Setting -> Bool
$c<= :: Setting -> Setting -> Bool
<= :: Setting -> Setting -> Bool
$c> :: Setting -> Setting -> Bool
> :: Setting -> Setting -> Bool
$c>= :: Setting -> Setting -> Bool
>= :: Setting -> Setting -> Bool
$cmax :: Setting -> Setting -> Setting
max :: Setting -> Setting -> Setting
$cmin :: Setting -> Setting -> Setting
min :: Setting -> Setting -> Setting
Ord, Int -> Setting -> ShowS
[Setting] -> ShowS
Setting -> String
(Int -> Setting -> ShowS)
-> (Setting -> String) -> ([Setting] -> ShowS) -> Show Setting
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Setting -> ShowS
showsPrec :: Int -> Setting -> ShowS
$cshow :: Setting -> String
show :: Setting -> String
$cshowList :: [Setting] -> ShowS
showList :: [Setting] -> ShowS
Show, ReadPrec [Setting]
ReadPrec Setting
Int -> ReadS Setting
ReadS [Setting]
(Int -> ReadS Setting)
-> ReadS [Setting]
-> ReadPrec Setting
-> ReadPrec [Setting]
-> Read Setting
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Setting
readsPrec :: Int -> ReadS Setting
$creadList :: ReadS [Setting]
readList :: ReadS [Setting]
$creadPrec :: ReadPrec Setting
readPrec :: ReadPrec Setting
$creadListPrec :: ReadPrec [Setting]
readListPrec :: ReadPrec [Setting]
Read)
setting :: Setting -> Ingredient
setting :: Setting -> Ingredient
setting Setting
x = (Setting -> Expr
forall a. (Typeable a, Show a) => a -> Expr
val Setting
x, String -> Reification
forall a. HasCallStack => String -> a
error String
"Conjure.Settings: evaluating reification, this is a bug")
extract :: Ingredient -> Setting
= Setting -> Expr -> Setting
forall a. Typeable a => a -> Expr -> a
eval Setting
Noop (Expr -> Setting) -> (Ingredient -> Expr) -> Ingredient -> Setting
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ingredient -> Expr
forall a b. (a, b) -> a
fst
actual :: [Ingredient] -> [Ingredient]
actual :: [Ingredient] -> [Ingredient]
actual [Ingredient]
is = [Ingredient
i | Ingredient
i <- [Ingredient]
is, Expr -> TypeRep
typ (Ingredient -> Expr
forall a b. (a, b) -> a
fst Ingredient
i) TypeRep -> TypeRep -> Bool
forall a. Eq a => a -> a -> Bool
/= Setting -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf Setting
Noop]
maxTests :: Int -> Ingredient
maxTests :: Int -> Ingredient
maxTests = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxTests
maxTestsI :: [Ingredient] -> Int
maxTestsI :: [Ingredient] -> Int
maxTestsI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
360 [Int
m | MaxTests Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxSize :: Int -> Ingredient
maxSize :: Int -> Ingredient
maxSize = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxSize
target :: Int -> Ingredient
target :: Int -> Ingredient
target = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
Target
targetAndMaxSizeI :: [Ingredient] -> (Int, Int)
targetAndMaxSizeI :: [Ingredient] -> (Int, Int)
targetAndMaxSizeI [Ingredient]
is =
case (Int
t, Int
m) of
(Int
0, Int
0) -> (Int
10080, Int
0)
(Int
t, Int
m) -> (Int
t, Int
m)
where
t :: Int
t = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
0 [Int
m | Target Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
m :: Int
m = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
0 [Int
m | MaxSize Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxRecursions :: Int -> Ingredient
maxRecursions :: Int -> Ingredient
maxRecursions = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxRecursions
maxRecursionsI :: [Ingredient] -> Int
maxRecursionsI :: [Ingredient] -> Int
maxRecursionsI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
60 [Int
m | MaxRecursions Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxEquationSize :: Int -> Ingredient
maxEquationSize :: Int -> Ingredient
maxEquationSize = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxEquationSize
maxEquationSizeI :: [Ingredient] -> Int
maxEquationSizeI :: [Ingredient] -> Int
maxEquationSizeI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
5 [Int
m | MaxEquationSize Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxSearchTests :: Int -> Ingredient
maxSearchTests :: Int -> Ingredient
maxSearchTests = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxSearchTests
maxSearchTestsI :: [Ingredient] -> Int
maxSearchTestsI :: [Ingredient] -> Int
maxSearchTestsI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
110880 [Int
m | MaxSearchTests Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxDeconstructionSize :: Int -> Ingredient
maxDeconstructionSize :: Int -> Ingredient
maxDeconstructionSize = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxDeconstructionSize
maxDeconstructionSizeI :: [Ingredient] -> Int
maxDeconstructionSizeI :: [Ingredient] -> Int
maxDeconstructionSizeI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
4 [Int
m | MaxDeconstructionSize Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxConstantSize :: Int -> Ingredient
maxConstantSize :: Int -> Ingredient
maxConstantSize = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxConstantSize
maxConstantSizeI :: [Ingredient] -> Int
maxConstantSizeI :: [Ingredient] -> Int
maxConstantSizeI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
0 [Int
m | MaxConstantSize Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxPatternSize :: Int -> Ingredient
maxPatternSize :: Int -> Ingredient
maxPatternSize = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxPatternSize
maxPatternSizeI :: [Ingredient] -> Int
maxPatternSizeI :: [Ingredient] -> Int
maxPatternSizeI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
0 [Int
m | MaxPatternSize Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
maxPatternDepth :: Int -> Ingredient
maxPatternDepth :: Int -> Ingredient
maxPatternDepth = Setting -> Ingredient
setting (Setting -> Ingredient) -> (Int -> Setting) -> Int -> Ingredient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Setting
MaxPatternDepth
maxPatternDepthI :: [Ingredient] -> Int
maxPatternDepthI :: [Ingredient] -> Int
maxPatternDepthI [Ingredient]
is = Int -> [Int] -> Int
forall a. a -> [a] -> a
headOr Int
1 [Int
m | MaxPatternDepth Int
m <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
carryOn :: Ingredient
carryOn :: Ingredient
carryOn = Setting -> Ingredient
setting Setting
CarryOn
carryOnI :: [Ingredient] -> Bool
carryOnI :: [Ingredient] -> Bool
carryOnI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
CarryOn <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
showTheory :: Ingredient
showTheory :: Ingredient
showTheory = Setting -> Ingredient
setting Setting
ShowTheory
showTheoryI :: [Ingredient] -> Bool
showTheoryI :: [Ingredient] -> Bool
showTheoryI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
ShowTheory <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
singlePattern :: Ingredient
singlePattern :: Ingredient
singlePattern = Setting -> Ingredient
setting Setting
SinglePattern
singlePatternI :: [Ingredient] -> Bool
singlePatternI :: [Ingredient] -> Bool
singlePatternI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
SinglePattern <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
showCandidates :: Ingredient
showCandidates :: Ingredient
showCandidates = Setting -> Ingredient
setting Setting
ShowCandidates
showCandidatesI :: [Ingredient] -> Bool
showCandidatesI :: [Ingredient] -> Bool
showCandidatesI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
ShowCandidates <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
showTests :: Ingredient
showTests :: Ingredient
showTests = Setting -> Ingredient
setting Setting
ShowTests
showTestsI :: [Ingredient] -> Bool
showTestsI :: [Ingredient] -> Bool
showTestsI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
ShowTests <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
showPatterns :: Ingredient
showPatterns :: Ingredient
showPatterns = Setting -> Ingredient
setting Setting
ShowPatterns
showPatternsI :: [Ingredient] -> Bool
showPatternsI :: [Ingredient] -> Bool
showPatternsI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
ShowPatterns <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
showDeconstructions :: Ingredient
showDeconstructions :: Ingredient
showDeconstructions = Setting -> Ingredient
setting Setting
ShowDeconstructions
showDeconstructionsI :: [Ingredient] -> Bool
showDeconstructionsI :: [Ingredient] -> Bool
showDeconstructionsI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
ShowDeconstructions <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
dontRewrite :: Ingredient
dontRewrite :: Ingredient
dontRewrite = Setting -> Ingredient
setting Setting
DontRewrite
rewriteI :: [Ingredient] -> Bool
rewriteI :: [Ingredient] -> Bool
rewriteI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Bool
False | Setting
DontRewrite <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
dontRequireDescent :: Ingredient
dontRequireDescent :: Ingredient
dontRequireDescent = Setting -> Ingredient
setting Setting
DontRequireDescent
requireDescentI :: [Ingredient] -> Bool
requireDescentI :: [Ingredient] -> Bool
requireDescentI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Bool
False | Setting
DontRequireDescent <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
omitAssortedPruning :: Ingredient
omitAssortedPruning :: Ingredient
omitAssortedPruning = Setting -> Ingredient
setting Setting
OmitAssortedPruning
assortedPruningI :: [Ingredient] -> Bool
assortedPruningI :: [Ingredient] -> Bool
assortedPruningI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Bool
False | Setting
OmitAssortedPruning <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
omitEarlyTests :: Ingredient
omitEarlyTests :: Ingredient
omitEarlyTests = Setting -> Ingredient
setting Setting
OmitEarlyTests
earlyTestsI :: [Ingredient] -> Bool
earlyTestsI :: [Ingredient] -> Bool
earlyTestsI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Bool
False | Setting
OmitEarlyTests <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
dontCopyBindings :: Ingredient
dontCopyBindings :: Ingredient
dontCopyBindings = Setting -> Ingredient
setting Setting
DontCopyBindings
copyBindingsI :: [Ingredient] -> Bool
copyBindingsI :: [Ingredient] -> Bool
copyBindingsI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Bool
False | Setting
DontCopyBindings <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
atomicNumbers :: Ingredient
atomicNumbers :: Ingredient
atomicNumbers = Setting -> Ingredient
setting Setting
AtomicNumbers
nonAtomicNumbers :: Ingredient
nonAtomicNumbers :: Ingredient
nonAtomicNumbers = Setting -> Ingredient
setting Setting
NonAtomicNumbers
atomicNumbersI :: [Ingredient] -> Bool
atomicNumbersI :: [Ingredient] -> Bool
atomicNumbersI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Bool
False | Setting
NonAtomicNumbers <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]
uniqueCandidates :: Ingredient
uniqueCandidates :: Ingredient
uniqueCandidates = Setting -> Ingredient
setting Setting
UniqueCandidates
uniqueCandidatesI :: [Ingredient] -> Bool
uniqueCandidatesI :: [Ingredient] -> Bool
uniqueCandidatesI [Ingredient]
is = [Bool] -> Bool
forall a. [a] -> Bool
notNull [Bool
True | Setting
UniqueCandidates <- (Ingredient -> Setting) -> [Ingredient] -> [Setting]
forall a b. (a -> b) -> [a] -> [b]
map Ingredient -> Setting
extract [Ingredient]
is]