{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Language.Haskell.Liquid.UX.Config (
Config (..)
, HasConfig (..)
, Verbosity (..)
, allowPLE, allowLocalPLE, allowGlobalPLE
, cmdargsVerbosity
, patternFlag
, higherOrderFlag
, pruneFlag
, maxCaseExpand
, exactDCFlag
, hasOpt
, totalityCheck
, terminationCheck
, structuralTerm
) where
import Prelude hiding (error)
import Language.Fixpoint.Types.Config hiding (Config)
import GHC.Generics
import System.Console.CmdArgs hiding (Verbosity(..))
import qualified System.Console.CmdArgs as CmdArgs
data Verbosity = Quiet | Minimal | Normal | Loud
deriving (Typeable Verbosity
Typeable Verbosity =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity)
-> (Verbosity -> Constr)
-> (Verbosity -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity))
-> ((forall b. Data b => b -> b) -> Verbosity -> Verbosity)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r)
-> (forall u. (forall d. Data d => d -> u) -> Verbosity -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Verbosity -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity)
-> Data Verbosity
Verbosity -> Constr
Verbosity -> DataType
(forall b. Data b => b -> b) -> Verbosity -> Verbosity
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Verbosity -> c Verbosity
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Verbosity
$ctoConstr :: Verbosity -> Constr
toConstr :: Verbosity -> Constr
$cdataTypeOf :: Verbosity -> DataType
dataTypeOf :: Verbosity -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Verbosity)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Verbosity)
$cgmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
gmapT :: (forall b. Data b => b -> b) -> Verbosity -> Verbosity
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Verbosity -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Verbosity -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Verbosity -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Verbosity -> m Verbosity
Data, (forall x. Verbosity -> Rep Verbosity x)
-> (forall x. Rep Verbosity x -> Verbosity) -> Generic Verbosity
forall x. Rep Verbosity x -> Verbosity
forall x. Verbosity -> Rep Verbosity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Verbosity -> Rep Verbosity x
from :: forall x. Verbosity -> Rep Verbosity x
$cto :: forall x. Rep Verbosity x -> Verbosity
to :: forall x. Rep Verbosity x -> Verbosity
Generic, Int -> Verbosity -> ShowS
[Verbosity] -> ShowS
Verbosity -> String
(Int -> Verbosity -> ShowS)
-> (Verbosity -> String)
-> ([Verbosity] -> ShowS)
-> Show Verbosity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Verbosity -> ShowS
showsPrec :: Int -> Verbosity -> ShowS
$cshow :: Verbosity -> String
show :: Verbosity -> String
$cshowList :: [Verbosity] -> ShowS
showList :: [Verbosity] -> ShowS
Show, Verbosity -> Verbosity -> Bool
(Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool) -> Eq Verbosity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Verbosity -> Verbosity -> Bool
== :: Verbosity -> Verbosity -> Bool
$c/= :: Verbosity -> Verbosity -> Bool
/= :: Verbosity -> Verbosity -> Bool
Eq, Eq Verbosity
Eq Verbosity =>
(Verbosity -> Verbosity -> Ordering)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Bool)
-> (Verbosity -> Verbosity -> Verbosity)
-> (Verbosity -> Verbosity -> Verbosity)
-> Ord Verbosity
Verbosity -> Verbosity -> Bool
Verbosity -> Verbosity -> Ordering
Verbosity -> Verbosity -> Verbosity
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 :: Verbosity -> Verbosity -> Ordering
compare :: Verbosity -> Verbosity -> Ordering
$c< :: Verbosity -> Verbosity -> Bool
< :: Verbosity -> Verbosity -> Bool
$c<= :: Verbosity -> Verbosity -> Bool
<= :: Verbosity -> Verbosity -> Bool
$c> :: Verbosity -> Verbosity -> Bool
> :: Verbosity -> Verbosity -> Bool
$c>= :: Verbosity -> Verbosity -> Bool
>= :: Verbosity -> Verbosity -> Bool
$cmax :: Verbosity -> Verbosity -> Verbosity
max :: Verbosity -> Verbosity -> Verbosity
$cmin :: Verbosity -> Verbosity -> Verbosity
min :: Verbosity -> Verbosity -> Verbosity
Ord)
cmdargsVerbosity :: Verbosity -> CmdArgs.Verbosity
cmdargsVerbosity :: Verbosity -> Verbosity
cmdargsVerbosity Verbosity
Quiet = Verbosity
CmdArgs.Quiet
cmdargsVerbosity Verbosity
Minimal = Verbosity
CmdArgs.Quiet
cmdargsVerbosity Verbosity
Normal = Verbosity
CmdArgs.Normal
cmdargsVerbosity Verbosity
Loud = Verbosity
CmdArgs.Loud
data Config = Config
{ Config -> Verbosity
loggingVerbosity :: Verbosity
, Config -> [String]
files :: [FilePath]
, Config -> [String]
idirs :: [FilePath]
, Config -> Bool
diffcheck :: Bool
, Config -> Bool
linear :: Bool
, Config -> Bool
stringTheory :: Bool
, Config -> Bool
higherorder :: Bool
, Config -> Bool
higherorderqs :: Bool
, Config -> Maybe Int
smtTimeout :: Maybe Int
, Config -> Bool
fullcheck :: Bool
, Config -> Bool
saveQuery :: Bool
, Config -> [String]
checks :: [String]
, Config -> Bool
noCheckUnknown :: Bool
, Config -> Bool
notermination :: Bool
, Config -> Bool
nopositivity :: Bool
, Config -> Bool
rankNTypes :: Bool
, Config -> Bool
noclasscheck :: Bool
, Config -> Bool
nostructuralterm :: Bool
, Config -> Bool
gradual :: Bool
, Config -> Bool
bscope :: Bool
, Config -> Int
gdepth :: Int
, Config -> Bool
ginteractive :: Bool
, Config -> Bool
totalHaskell :: Bool
, Config -> Bool
nowarnings :: Bool
, Config -> Bool
noannotations :: Bool
, Config -> Bool
checkDerived :: Bool
, Config -> Int
caseExpandDepth :: Int
, Config -> Bool
notruetypes :: Bool
, Config -> Bool
nototality :: Bool
, Config -> Bool
pruneUnsorted :: Bool
, Config -> Maybe Int
cores :: Maybe Int
, Config -> Int
minPartSize :: Int
, Config -> Int
maxPartSize :: Int
, Config -> Int
maxParams :: Int
, Config -> Maybe SMTSolver
smtsolver :: Maybe SMTSolver
, Config -> Bool
shortNames :: Bool
, Config -> Bool
shortErrors :: Bool
, Config -> Bool
cabalDir :: Bool
, Config -> [String]
ghcOptions :: [String]
, Config -> [String]
cFiles :: [String]
, Config -> Eliminate
eliminate :: Eliminate
, Config -> Int
port :: Int
, Config -> Bool
exactDC :: Bool
, Config -> Bool
noADT :: Bool
, Config -> [String]
expectErrorContaining :: [String]
, Config -> Bool
expectAnyError :: Bool
, Config -> Bool
scrapeInternals :: Bool
, Config -> Bool
elimStats :: Bool
, Config -> Maybe Int
elimBound :: Maybe Int
, Config -> Bool
json :: Bool
, Config -> Bool
counterExamples :: Bool
, Config -> Bool
timeBinds :: Bool
, Config -> Bool
noPatternInline :: Bool
, Config -> Bool
untidyCore :: Bool
, Config -> Bool
noSimplifyCore :: Bool
, Config -> Bool
noslice :: Bool
, Config -> Bool
noLiftedImport :: Bool
, Config -> Bool
proofLogicEval :: Bool
, Config -> Bool
pleWithUndecidedGuards :: Bool
, Config -> Bool
oldPLE :: Bool
, Config -> Bool
interpreter :: Bool
, Config -> Bool
proofLogicEvalLocal :: Bool
, Config -> Bool
etabeta :: Bool
, Config -> Bool
dependantCase :: Bool
, Config -> Bool
extensionality :: Bool
, Config -> Bool
nopolyinfer :: Bool
, Config -> Bool
reflection :: Bool
, Config -> Bool
compileSpec :: Bool
, Config -> Bool
noCheckImports :: Bool
, Config -> Bool
typeclass :: Bool
, Config -> Bool
auxInline :: Bool
, Config -> Bool
rwTerminationCheck :: Bool
, Config -> Bool
skipModule :: Bool
, Config -> Bool
noLazyPLE :: Bool
, Config -> Maybe Int
fuel :: Maybe Int
, Config -> Bool
environmentReduction :: Bool
, Config -> Bool
noEnvironmentReduction :: Bool
, Config -> Bool
inlineANFBindings :: Bool
, Config -> Bool
pandocHtml :: Bool
, Config -> [String]
excludeAutomaticAssumptionsFor :: [String]
, Config -> Bool
dumpOpaqueReflections :: Bool
, Config -> Bool
dumpPreNormalizedCore :: Bool
, Config -> Bool
allowUnsafeConstructors :: Bool
} deriving ((forall x. Config -> Rep Config x)
-> (forall x. Rep Config x -> Config) -> Generic Config
forall x. Rep Config x -> Config
forall x. Config -> Rep Config x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Config -> Rep Config x
from :: forall x. Config -> Rep Config x
$cto :: forall x. Rep Config x -> Config
to :: forall x. Rep Config x -> Config
Generic, Typeable Config
Typeable Config =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config)
-> (Config -> Constr)
-> (Config -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config))
-> ((forall b. Data b => b -> b) -> Config -> Config)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Config -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Config -> r)
-> (forall u. (forall d. Data d => d -> u) -> Config -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Config -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config)
-> Data Config
Config -> Constr
Config -> DataType
(forall b. Data b => b -> b) -> Config -> Config
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
forall u. (forall d. Data d => d -> u) -> Config -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
$ctoConstr :: Config -> Constr
toConstr :: Config -> Constr
$cdataTypeOf :: Config -> DataType
dataTypeOf :: Config -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
$cgmapT :: (forall b. Data b => b -> b) -> Config -> Config
gmapT :: (forall b. Data b => b -> b) -> Config -> Config
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Config -> m Config
Data, Typeable, Int -> Config -> ShowS
[Config] -> ShowS
Config -> String
(Int -> Config -> ShowS)
-> (Config -> String) -> ([Config] -> ShowS) -> Show Config
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Config -> ShowS
showsPrec :: Int -> Config -> ShowS
$cshow :: Config -> String
show :: Config -> String
$cshowList :: [Config] -> ShowS
showList :: [Config] -> ShowS
Show, Config -> Config -> Bool
(Config -> Config -> Bool)
-> (Config -> Config -> Bool) -> Eq Config
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
/= :: Config -> Config -> Bool
Eq)
allowPLE :: Config -> Bool
allowPLE :: Config -> Bool
allowPLE Config
cfg
= Config -> Bool
allowGlobalPLE Config
cfg
Bool -> Bool -> Bool
|| Config -> Bool
allowLocalPLE Config
cfg
allowGlobalPLE :: Config -> Bool
allowGlobalPLE :: Config -> Bool
allowGlobalPLE Config
cfg = Config -> Bool
proofLogicEval Config
cfg
allowLocalPLE :: Config -> Bool
allowLocalPLE :: Config -> Bool
allowLocalPLE Config
cfg = Config -> Bool
proofLogicEvalLocal Config
cfg
instance HasConfig Config where
getConfig :: Config -> Config
getConfig Config
x = Config
x
class HasConfig t where
getConfig :: t -> Config
patternFlag :: (HasConfig t) => t -> Bool
patternFlag :: forall t. HasConfig t => t -> Bool
patternFlag = Bool -> Bool
not (Bool -> Bool) -> (t -> Bool) -> t -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Bool
noPatternInline (Config -> Bool) -> (t -> Config) -> t -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Config
forall t. HasConfig t => t -> Config
getConfig
higherOrderFlag :: (HasConfig t) => t -> Bool
higherOrderFlag :: forall t. HasConfig t => t -> Bool
higherOrderFlag t
x = Config -> Bool
higherorder Config
cfg Bool -> Bool -> Bool
|| Config -> Bool
reflection Config
cfg
where
cfg :: Config
cfg = t -> Config
forall t. HasConfig t => t -> Config
getConfig t
x
exactDCFlag :: (HasConfig t) => t -> Bool
exactDCFlag :: forall t. HasConfig t => t -> Bool
exactDCFlag t
x = Config -> Bool
exactDC Config
cfg Bool -> Bool -> Bool
|| Config -> Bool
reflection Config
cfg
where
cfg :: Config
cfg = t -> Config
forall t. HasConfig t => t -> Config
getConfig t
x
pruneFlag :: (HasConfig t) => t -> Bool
pruneFlag :: forall t. HasConfig t => t -> Bool
pruneFlag = Config -> Bool
pruneUnsorted (Config -> Bool) -> (t -> Config) -> t -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Config
forall t. HasConfig t => t -> Config
getConfig
maxCaseExpand :: (HasConfig t) => t -> Int
maxCaseExpand :: forall t. HasConfig t => t -> Int
maxCaseExpand = Config -> Int
caseExpandDepth (Config -> Int) -> (t -> Config) -> t -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Config
forall t. HasConfig t => t -> Config
getConfig
hasOpt :: (HasConfig t) => t -> (Config -> Bool) -> Bool
hasOpt :: forall t. HasConfig t => t -> (Config -> Bool) -> Bool
hasOpt t
t Config -> Bool
f = Config -> Bool
f (t -> Config
forall t. HasConfig t => t -> Config
getConfig t
t)
totalityCheck :: (HasConfig t) => t -> Bool
totalityCheck :: forall t. HasConfig t => t -> Bool
totalityCheck = Config -> Bool
totalityCheck' (Config -> Bool) -> (t -> Config) -> t -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Config
forall t. HasConfig t => t -> Config
getConfig
terminationCheck :: (HasConfig t) => t -> Bool
terminationCheck :: forall t. HasConfig t => t -> Bool
terminationCheck = Config -> Bool
terminationCheck' (Config -> Bool) -> (t -> Config) -> t -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Config
forall t. HasConfig t => t -> Config
getConfig
totalityCheck' :: Config -> Bool
totalityCheck' :: Config -> Bool
totalityCheck' Config
cfg = Bool -> Bool
not (Config -> Bool
nototality Config
cfg) Bool -> Bool -> Bool
|| Config -> Bool
totalHaskell Config
cfg
terminationCheck' :: Config -> Bool
terminationCheck' :: Config -> Bool
terminationCheck' Config
cfg = Config -> Bool
totalHaskell Config
cfg Bool -> Bool -> Bool
|| Bool -> Bool
not (Config -> Bool
notermination Config
cfg)
structuralTerm :: (HasConfig a) => a -> Bool
structuralTerm :: forall t. HasConfig t => t -> Bool
structuralTerm = Bool -> Bool
not (Bool -> Bool) -> (a -> Bool) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Bool
nostructuralterm (Config -> Bool) -> (a -> Config) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Config
forall t. HasConfig t => t -> Config
getConfig