crux-0.7: Simple top-level library for Crucible Simulation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crux

Synopsis

Documentation

runSimulator :: Logs msgs => SupportsCruxLogMessage msgs => CruxOptions -> SimulatorCallbacks msgs r -> IO r Source #

Parse through all of the user-provided options and start up the verification process

This figures out which solvers need to be run, and in which modes. It takes as arguments some of the results of common setup code. It also tries to minimize code duplication between the different verification paths (e.g., online vs offline solving).

postprocessSimResult :: Logs msgs => Bool -> CruxOptions -> CruxSimulationResult -> IO ExitCode Source #

Given the result of a simulation and proof run, report the overall status, generate user-consumable reports and compute the exit code.

loadOptions Source #

Arguments

:: SupportsCruxLogMessage msgs 
=> (Maybe OutputOptions -> OutputConfig msgs) 
-> Text

Name

-> Version 
-> Config opts 
-> (Logs msgs => (CruxOptions, opts) -> IO a) 
-> IO a 

Load crux generic and the provided options, and provide them to the given continuation.

IMPORTANT: This processes options like help and version, which just print something and exit, so this function may never call its continuation.

mkOutputConfig :: ToJSON msgs => (Handle, Bool) -> (Handle, Bool) -> (msgs -> SayWhat) -> Maybe OutputOptions -> OutputConfig msgs Source #

Create an OutputConfig for Crux, based on an indication of whether colored output should be used, the normal and error output handles, and the parsed CruxOptions.

If no CruxOptions are available (i.e. Nothing, as used in the preliminary portions of loadOptions), then a default output stance is applied; the default stance is described along with the individual option below.

The following CruxOptions affect the generated OutputConfig:

  • noColorsErr (default stance: False when the error handle supports colors, as reported by System.Console.ANSI.hSupportsANSIColor)
  • noColorsOut (default stance: False when the output handle supports colors, as reported by System.Console.ANSI.hSupportsANSIColor)
  • printFailures (default stance: True)
  • quietMode (default stance: False)
  • simVerbose (default stance: False)

newtype SimulatorCallbacks msgs r Source #

Individual crux tools will generally call the runSimulator combinator to handle the nitty-gritty of setting up and running the simulator. Tools provide SimulatorCallbacks to hook into the simulation process at three points:

  • Before simulation begins, to set up global variables, register override functions, construct the initial program entry point, and generally do any necessary language-specific setup (i.e., to produce a RunnableState)
  • When simulation ends with an assertion failure (Explainer)
  • When simulation ends, regardless of the outcome, to interpret the results.

All of these callbacks have access to the symbolic backend.

Constructors

SimulatorCallbacks 

Fields

data SimulatorHooks sym bak t r Source #

Constructors

SimulatorHooks 

Fields

data RunnableState sym where Source #

A crucible ExecState that is ready to be passed into the simulator. This will usually, but not necessarily, be an InitialState.

Constructors

RunnableStateWithExtensions :: IsSyntaxExtension ext => ExecState (personality sym) sym ext (RegEntry sym UnitType) -> [ExecutionFeature (personality sym) sym ext (RegEntry sym UnitType)] -> RunnableState sym 

pattern RunnableState :: forall sym. () => forall ext personality. IsSyntaxExtension ext => ExecState (personality sym) sym ext (RegEntry sym UnitType) -> RunnableState sym Source #

type Explainer sym t ann = Maybe (GroundEvalFn t) -> LPred sym SimError -> IO (Doc ann) Source #

A function that can be used to generate a pretty explanation of a simulation error.

data CruxOptions Source #

Common options for Crux-based binaries.

Constructors

CruxOptions 

Fields

Instances

Instances details
Generic CruxOptions Source # 
Instance details

Defined in Crux.Config.Common

Associated Types

type Rep CruxOptions :: Type -> Type #

type Rep CruxOptions Source # 
Instance details

Defined in Crux.Config.Common

type Rep CruxOptions = D1 ('MetaData "CruxOptions" "Crux.Config.Common" "crux-0.7-DD4jascIe8aJ5p2f7vnjLq" 'False) (C1 ('MetaCons "CruxOptions" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "inputFiles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FilePath]) :*: (S1 ('MetaSel ('Just "outDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "bldDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))) :*: ((S1 ('MetaSel ('Just "checkPathSat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "profileCrucibleFunctions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "profileSolver") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "branchCoverage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: (((S1 ('MetaSel ('Just "pathStrategy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PathStrategy) :*: S1 ('MetaSel ('Just "globalTimeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NominalDiffTime))) :*: (S1 ('MetaSel ('Just "goalTimeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DiffTime)) :*: S1 ('MetaSel ('Just "profileOutputInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NominalDiffTime))) :*: ((S1 ('MetaSel ('Just "loopBound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64)) :*: S1 ('MetaSel ('Just "recursionBound") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64))) :*: (S1 ('MetaSel ('Just "makeCexes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "unsatCores") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :*: ((((S1 ('MetaSel ('Just "getNAbducts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Word64)) :*: S1 ('MetaSel ('Just "solver") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "pathSatSolver") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)) :*: S1 ('MetaSel ('Just "forceOfflineGoalSolving") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "pathSatSolverOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "onlineSolverOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))) :*: (S1 ('MetaSel ('Just "offlineSolverOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath)) :*: S1 ('MetaSel ('Just "yicesMCSat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: (((S1 ('MetaSel ('Just "floatMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "proofGoalsFailFast") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "skipReport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "skipSuccessReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "skipIncompleteReports") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "hashConsing") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "onlineProblemFeatures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProblemFeatures) :*: S1 ('MetaSel ('Just "outputOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OutputOptions)))))))

data SomeOnlineSolver sym bak where Source #

A GADT to capture the online solver constraints when we need them

Constructors

SomeOnlineSolver :: (sym ~ ExprBuilder scope st fs, bak ~ OnlineBackend solver scope st fs, IsSymBackend sym bak, OnlineSolver solver) => bak -> SomeOnlineSolver sym bak 

data Crux sym Source #

A dummy datatype that can be used for the "personality" type parameter.

Constructors

CruxPersonality 

module Crux.Log

module Crux.Log