module Language.Haskell.Liquid.UX.Config (
Config (..)
, HasConfig (..)
, Instantiate (..)
, allowSMTInstationation
, allowLiquidInstationation
, allowLiquidInstationationGlobal
, allowLiquidInstationationLocal
, ProofMethod (..)
, allowRewrite
) where
import Prelude hiding (error)
import Data.Serialize ( Serialize )
import Language.Fixpoint.Types.Config hiding (Config)
import GHC.Generics
import System.Console.CmdArgs
data Config = Config {
files :: [FilePath]
, idirs :: [FilePath]
, diffcheck :: Bool
, linear :: Bool
, stringTheory :: Bool
, higherorder :: Bool
, higherorderqs :: Bool
, extensionality :: Bool
, alphaEquivalence :: Bool
, betaEquivalence :: Bool
, normalForm :: Bool
, fullcheck :: Bool
, saveQuery :: Bool
, checks :: [String]
, noCheckUnknown :: Bool
, notermination :: Bool
, gradual :: Bool
, ginteractive :: Bool
, totalHaskell :: Bool
, autoproofs :: Bool
, nowarnings :: Bool
, noannotations :: Bool
, trustInternals :: Bool
, nocaseexpand :: Bool
, strata :: Bool
, notruetypes :: Bool
, nototality :: Bool
, pruneUnsorted :: Bool
, cores :: Maybe Int
, minPartSize :: Int
, maxPartSize :: Int
, maxParams :: Int
, smtsolver :: Maybe SMTSolver
, shortNames :: Bool
, shortErrors :: Bool
, cabalDir :: Bool
, ghcOptions :: [String]
, cFiles :: [String]
, eliminate :: Eliminate
, port :: Int
, exactDC :: Bool
, noADT :: Bool
, noMeasureFields :: Bool
, scrapeImports :: Bool
, scrapeInternals :: Bool
, scrapeUsedImports :: Bool
, elimStats :: Bool
, elimBound :: Maybe Int
, json :: Bool
, counterExamples :: Bool
, timeBinds :: Bool
, noPatternInline :: Bool
, untidyCore :: Bool
, noSimplifyCore :: Bool
, nonLinCuts :: Bool
, autoInstantiate :: Instantiate
, proofMethod :: ProofMethod
, fuel :: Int
, debugInstantionation :: Bool
, noslice :: Bool
, noLiftedImport :: Bool
} deriving (Generic, Data, Typeable, Show, Eq)
instance Serialize ProofMethod
instance Serialize Instantiate
instance Serialize SMTSolver
instance Serialize Config
data Instantiate = NoInstances | SMTInstances | LiquidInstances | LiquidInstancesLocal
deriving (Eq, Data, Typeable, Generic)
data ProofMethod = Rewrite | AllMethods
deriving (Eq, Data, Typeable, Generic)
allowSMTInstationation, allowLiquidInstationation, allowLiquidInstationationLocal, allowLiquidInstationationGlobal :: Config -> Bool
allowSMTInstationation cfg = autoInstantiate cfg == SMTInstances
allowLiquidInstationation cfg = autoInstantiate cfg == LiquidInstances
|| autoInstantiate cfg == LiquidInstancesLocal
allowLiquidInstationationGlobal cfg = autoInstantiate cfg == LiquidInstances
allowLiquidInstationationLocal cfg = autoInstantiate cfg == LiquidInstancesLocal
allowInstances, allowRewrite :: Config -> Bool
allowRewrite cfg = allowInstances cfg && (proofMethod cfg == Rewrite || proofMethod cfg == AllMethods)
allowInstances cfg = autoInstantiate cfg /= NoInstances
instance Default ProofMethod where
def = Rewrite
instance Show ProofMethod where
show Rewrite = "rewrite"
show AllMethods = "all"
instance Default Instantiate where
def = NoInstances
instance Show Instantiate where
show NoInstances = "none"
show SMTInstances = "SMT"
show LiquidInstancesLocal = "liquid-local"
show LiquidInstances = "liquid-global"
instance HasConfig Config where
getConfig x = x
class HasConfig t where
getConfig :: t -> Config
patternFlag :: t -> Bool
patternFlag = not . noPatternInline . getConfig
higherOrderFlag :: t -> Bool
higherOrderFlag = higherorder . getConfig
pruneFlag :: t -> Bool
pruneFlag = pruneUnsorted . getConfig
expandFlag :: t -> Bool
expandFlag = not . nocaseexpand . getConfig
hasOpt :: t -> (Config -> Bool) -> Bool
hasOpt t f = f (getConfig t)
totalityCheck :: t -> Bool
totalityCheck = totalityCheck' . getConfig
terminationCheck :: t -> Bool
terminationCheck = terminationCheck' . getConfig
totalityCheck' :: Config -> Bool
totalityCheck' cfg = (not (nototality cfg)) || totalHaskell cfg
terminationCheck' :: Config -> Bool
terminationCheck' cfg = totalHaskell cfg || not (notermination cfg)