Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Crux.Types
Synopsis
- type SimCtxt personality sym p = SimContext (personality sym) sym p
- type OverM personality sym ext a = forall r args ret. OverrideSim (personality sym) sym ext r args ret a
- type Fun personality sym ext args ret = forall r. OverrideSim (personality sym) sym ext r args ret (RegValue sym ret)
- data Result personality sym where
- Result :: ExecResult (personality sym) sym ext (RegEntry sym UnitType) -> Result personality sym
- data ProcessedGoals = ProcessedGoals {}
- data ProofResult sym
- = Proved [Either (Assumption sym) (Assertion sym)]
- | NotProved (Doc Void) (Maybe (ModelView, [CrucibleEvent GroundValueWrapper])) [String]
- type LPred sym = LabeledPred (Pred sym)
- data ProvedGoals
- = Branch ProvedGoals ProvedGoals
- | NotProvedGoal [CrucibleAssumption (Const ())] SimError (Doc Void) [ProgramLoc] (Maybe (ModelView, [CrucibleEvent GroundValueWrapper])) [String]
- | ProvedGoal [CrucibleAssumption (Const ())] SimError [ProgramLoc] Bool
- data ProgramCompleteness
- data CruxSimulationResult = CruxSimulationResult {}
- data Crux sym = CruxPersonality
- newtype Vals ty = Vals [Entry (GroundValue ty)]
- data Entry a = Entry {
- entryName :: String
- entryLoc :: ProgramLoc
- entryValue :: a
- newtype ModelView = ModelView {}
- data SayWhat
- data SayLevel
Documentation
type SimCtxt personality sym p = SimContext (personality sym) sym p Source #
A simulator context
type OverM personality sym ext a = forall r args ret. OverrideSim (personality sym) sym ext r args ret a Source #
The instance of the override monad we use, when we don't care about the context of the surrounding function.
type Fun personality sym ext args ret = forall r. OverrideSim (personality sym) sym ext r args ret (RegValue sym ret) Source #
This is the instance of the OverrideSim
monad that we use.
data Result personality sym where Source #
Constructors
Result :: ExecResult (personality sym) sym ext (RegEntry sym UnitType) -> Result personality sym |
data ProcessedGoals Source #
Constructors
ProcessedGoals | |
Fields
|
data ProofResult sym Source #
Constructors
Proved [Either (Assumption sym) (Assertion sym)] | |
NotProved (Doc Void) (Maybe (ModelView, [CrucibleEvent GroundValueWrapper])) [String] | The first argument is an explanation of the failure and counter example as provided by the Explainer (if any), the second maybe a model for the counter-example, and the third is a list of abducts provided which may be empty |
type LPred sym = LabeledPred (Pred sym) Source #
data ProvedGoals Source #
Constructors
Branch ProvedGoals ProvedGoals | |
NotProvedGoal [CrucibleAssumption (Const ())] SimError (Doc Void) [ProgramLoc] (Maybe (ModelView, [CrucibleEvent GroundValueWrapper])) [String] | |
ProvedGoal [CrucibleAssumption (Const ())] SimError [ProgramLoc] Bool | Keeps only the explanations for the relevant assumptions.
|
data ProgramCompleteness Source #
Constructors
ProgramComplete | |
ProgramIncomplete |
Instances
Show ProgramCompleteness Source # | |
Defined in Crux.Types Methods showsPrec :: Int -> ProgramCompleteness -> ShowS # show :: ProgramCompleteness -> String # showList :: [ProgramCompleteness] -> ShowS # | |
Eq ProgramCompleteness Source # | |
Defined in Crux.Types Methods (==) :: ProgramCompleteness -> ProgramCompleteness -> Bool # (/=) :: ProgramCompleteness -> ProgramCompleteness -> Bool # | |
Ord ProgramCompleteness Source # | |
Defined in Crux.Types Methods compare :: ProgramCompleteness -> ProgramCompleteness -> Ordering # (<) :: ProgramCompleteness -> ProgramCompleteness -> Bool # (<=) :: ProgramCompleteness -> ProgramCompleteness -> Bool # (>) :: ProgramCompleteness -> ProgramCompleteness -> Bool # (>=) :: ProgramCompleteness -> ProgramCompleteness -> Bool # max :: ProgramCompleteness -> ProgramCompleteness -> ProgramCompleteness # min :: ProgramCompleteness -> ProgramCompleteness -> ProgramCompleteness # |
data CruxSimulationResult Source #
Constructors
CruxSimulationResult | |
A dummy datatype that can be used for the "personality" type parameter.
Constructors
CruxPersonality |
A list of named GroundValues of the same type (used to report SMT models in a portable way -- see the ModelView datatype).
Constructors
Vals [Entry (GroundValue ty)] |
A named value of type a
with a program
location. Used to describe and report models from SMT
queries (see Model and ModelView datatypes).
Constructors
Entry | |
Fields
|
A portable/concrete view of a model's contents, organized by crucible type. I.e., each crucible type is associated with the list of entries (i.e. named GroundValues) at that type for the given model, used to describe the conditions under which an SMT query is satisfiable.
Constructors
ModelView | |
Fields |
Specify some general text that should be presented (to the user).