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

Crux.Config.Solver

Synopsis

Documentation

parseSolverConfig :: CruxOptions -> Either [String] SolverConfig Source #

Examine a CruxOptions and determine what solver configuration to use for symbolic execution. This can fail if an invalid solver configuration is requested by the user.

The high level logic is that:

  • If a user specifies only a single solver with the --solver option, that is used as an online solver if possible for path sat checking (if requested) and goal discharge.
  • If the user specifies an explicit --path-sat-solver, that solver is used for path satisfiability checking (if requested) while the solver specified with --solver is used for goal discharge.
  • The goal solver can be entirely offline (if it doesn't support online mode) or if the user requests that it be used in offline mode with the
  • -force-offline-goal-solving option.

data SolverConfig Source #

Constructors

SingleOnlineSolver SolverOnline

Use a single online solver for both path satisfiability checking and goal discharge

OnlineSolverWithOfflineGoals SolverOnline SolverOffline

Use an online solver for path satisfiability checking and use an offline solver for goal discharge

OnlineSolverWithSeparateOnlineGoals SolverOnline SolverOnline

Use one online solver connection for path satisfiability checking and a separate online solver connection for goal discharge. INVARIANT: the solvers must be distinct.

OnlyOfflineSolvers [SolverOffline]

Try any of a number of offline solvers with no support for path satisfiability checking

class HasDefaultFloatRepr solver where Source #

Methods

withDefaultFloatRepr :: st s -> solver -> (forall fm. IsInterpretedFloatExprBuilder (ExprBuilder s st (Flags fm)) => FloatModeRepr fm -> a) -> a Source #

Instances

Instances details
HasDefaultFloatRepr SolverOffline Source # 
Instance details

Defined in Crux.Config.Solver

Methods

withDefaultFloatRepr :: st s -> SolverOffline -> (forall (fm :: FloatMode). IsInterpretedFloatExprBuilder (ExprBuilder s st (Flags fm)) => FloatModeRepr fm -> a) -> a Source #

HasDefaultFloatRepr SolverOnline Source # 
Instance details

Defined in Crux.Config.Solver

Methods

withDefaultFloatRepr :: st s -> SolverOnline -> (forall (fm :: FloatMode). IsInterpretedFloatExprBuilder (ExprBuilder s st (Flags fm)) => FloatModeRepr fm -> a) -> a Source #

sameSolver :: SolverOnline -> SolverOffline -> Bool Source #

Test to see if an online and offline solver are actually the same