{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
module Language.Haskell.Liquid.UX.Config (
Config (..)
, HasConfig (..)
, allowPLE, allowLocalPLE, allowGlobalPLE
, 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
data Config = Config
{ Config -> Verbosity
loggingVerbosity :: Verbosity
, Config -> [FilePath]
files :: [FilePath]
, Config -> [FilePath]
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 -> [FilePath]
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 -> [FilePath]
ghcOptions :: [String]
, Config -> [FilePath]
cFiles :: [String]
, Config -> Eliminate
eliminate :: Eliminate
, Config -> Int
port :: Int
, Config -> Bool
exactDC :: Bool
, Config -> Bool
noADT :: Bool
, Config -> [FilePath]
expectErrorContaining :: [String]
, Config -> Bool
expectAnyError :: Bool
, Config -> Bool
scrapeImports :: Bool
, Config -> Bool
scrapeInternals :: Bool
, Config -> Bool
scrapeUsedImports :: 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
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 -> [FilePath]
excludeAutomaticAssumptionsFor :: [String]
} deriving (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
$cto :: forall x. Rep Config x -> Config
$cfrom :: forall x. Config -> Rep Config x
Generic, Typeable Config
Config -> DataType
Config -> Constr
(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)
gmapMo :: 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
gmapMp :: forall (m :: * -> *).
MonadPlus 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
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Config -> m Config
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Config -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Config -> [u]
gmapQr :: 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
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Config -> r
gmapT :: (forall b. Data b => b -> b) -> Config -> Config
$cgmapT :: (forall b. Data b => b -> b) -> Config -> Config
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Config)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Config)
dataTypeOf :: Config -> DataType
$cdataTypeOf :: Config -> DataType
toConstr :: Config -> Constr
$ctoConstr :: Config -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Config
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Config -> c Config
Data, Typeable, Int -> Config -> ShowS
[Config] -> ShowS
Config -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Config] -> ShowS
$cshowList :: [Config] -> ShowS
show :: Config -> FilePath
$cshow :: Config -> FilePath
showsPrec :: Int -> Config -> ShowS
$cshowsPrec :: Int -> Config -> ShowS
Show, Config -> Config -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Config -> Config -> Bool
$c/= :: Config -> Config -> Bool
== :: Config -> Config -> Bool
$c== :: 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Bool
noPatternInline forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 = 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 = 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. HasConfig t => t -> Config
getConfig
maxCaseExpand :: (HasConfig t) => t -> Int
maxCaseExpand :: forall t. HasConfig t => t -> Int
maxCaseExpand = Config -> Int
caseExpandDepth forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (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' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. HasConfig t => t -> Config
getConfig
terminationCheck :: (HasConfig t) => t -> Bool
terminationCheck :: forall t. HasConfig t => t -> Bool
terminationCheck = Config -> Bool
terminationCheck' forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Bool
nostructuralterm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. HasConfig t => t -> Config
getConfig