crucible-0.7: Crucible is a library for language-agnostic symbolic simulation
Copyright(c) Galois Inc 2014-2022
LicenseBSD3
MaintainerJoe Hendrix <jhendrix@galois.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.Backend

Description

This module provides an interface that symbolic backends must provide for interacting with the symbolic simulator.

Compared to the solver connections provided by What4, Crucible backends provide a facility for managing an assumption stack (see AssumptionStack). Note that these backends are layered on top of the ExprBuilder; the solver choice is still up to the user. The SimpleBackend is designed to be used with an offline solver connection, while the OnlineBackend is designed to be used with an online solver.

The AssumptionStack tracks the assumptions that are in scope for each assertion, accounting for the branching and merging structure of programs. The symbolic simulator manages the AssumptionStack. After symbolic simulation completes, the caller should traverse the AssumptionStack (or use combinators like proofGoalsToList) to discharge the resulting proof obligations with a solver backend.

Synopsis

Documentation

class (IsSymInterface sym, HasSymInterface sym bak) => IsSymBackend sym bak | bak -> sym where Source #

This class provides operations that interact with the symbolic simulator. It allows for logical assumptions/assertions to be added to the current path condition, and allows queries to be asked about branch conditions.

The bak type contains all the datastructures necessary to maintain the current program path conditions, and keep track of assumptions and assertions made during program execution. The sym type is expected to satisfy the IsSymInterface constraints, which provide access to the What4 expression language. A sym is uniquely determined by a bak.

Methods

pushAssumptionFrame :: bak -> IO FrameIdentifier Source #

Push a new assumption frame onto the stack. Assumptions and assertions made will now be associated with this frame on the stack until a new frame is pushed onto the stack, or until this one is popped.

popAssumptionFrame :: bak -> FrameIdentifier -> IO (Assumptions sym) Source #

Pop an assumption frame from the stack. The collected assumptions in this frame are returned. Pops are required to be well-bracketed with pushes. In particular, if the given frame identifier is not the identifier of the top frame on the stack, an error will be raised.

popUntilAssumptionFrame :: bak -> FrameIdentifier -> IO () Source #

Pop all assumption frames up to and including the frame with the given frame identifier. This operation will panic if the named frame does not exist on the stack.

popAssumptionFrameAndObligations :: bak -> FrameIdentifier -> IO (Assumptions sym, ProofObligations sym) Source #

Pop an assumption frame from the stack. The collected assummptions in this frame are returned, along with any proof obligations that were incurred while the frame was active. Pops are required to be well-bracketed with pushes. In particular, if the given frame identifier is not the identifier of the top frame on the stack, an error will be raised.

addAssumption :: bak -> Assumption sym -> IO () Source #

Add an assumption to the current state.

addAssumptions :: bak -> Assumptions sym -> IO () Source #

Add a collection of assumptions to the current state.

getPathCondition :: bak -> IO (Pred sym) Source #

Get the current path condition as a predicate. This consists of the conjunction of all the assumptions currently in scope.

collectAssumptions :: bak -> IO (Assumptions sym) Source #

Collect all the assumptions currently in scope

addProofObligation :: bak -> Assertion sym -> IO () Source #

Add a new proof obligation to the system. The proof may use the current path condition and assumptions. Note that this *DOES NOT* add the goal as an assumption. See also addAssertion. Also note that predicates that concretely evaluate to True will be silently discarded. See addDurableProofObligation to avoid discarding goals.

addDurableProofObligation :: bak -> Assertion sym -> IO () Source #

Add a new proof obligation to the system which will persist throughout symbolic execution even if it is concretely valid. The proof may use the current path condition and assumptions. Note that this *DOES NOT* add the goal as an assumption. See also addDurableAssertion.

getProofObligations :: bak -> IO (ProofObligations sym) Source #

Get the collection of proof obligations.

clearProofObligations :: bak -> IO () Source #

Forget the current collection of proof obligations. Presumably, we've already used getProofObligations to save them somewhere else.

saveAssumptionState :: bak -> IO (AssumptionState sym) Source #

Create a snapshot of the current assumption state, that may later be restored. This is useful for supporting control-flow patterns that don't neatly fit into the stack push/pop model.

restoreAssumptionState :: bak -> AssumptionState sym -> IO () Source #

Restore the assumption state to a previous snapshot.

resetAssumptionState :: bak -> IO () Source #

Reset the assumption state to a fresh, blank state

Instances

Instances details
IsSymInterface (ExprBuilder t st fs) => IsSymBackend (ExprBuilder t st fs) (SimpleBackend t st fs) Source # 
Instance details

Defined in Lang.Crucible.Backend.Simple

(IsSymInterface (ExprBuilder scope st fs), OnlineSolver solver) => IsSymBackend (ExprBuilder scope st fs) (OnlineBackend solver scope st fs) Source # 
Instance details

Defined in Lang.Crucible.Backend.Online

Methods

pushAssumptionFrame :: OnlineBackend solver scope st fs -> IO FrameIdentifier Source #

popAssumptionFrame :: OnlineBackend solver scope st fs -> FrameIdentifier -> IO (Assumptions (ExprBuilder scope st fs)) Source #

popUntilAssumptionFrame :: OnlineBackend solver scope st fs -> FrameIdentifier -> IO () Source #

popAssumptionFrameAndObligations :: OnlineBackend solver scope st fs -> FrameIdentifier -> IO (Assumptions (ExprBuilder scope st fs), ProofObligations (ExprBuilder scope st fs)) Source #

addAssumption :: OnlineBackend solver scope st fs -> Assumption (ExprBuilder scope st fs) -> IO () Source #

addAssumptions :: OnlineBackend solver scope st fs -> Assumptions (ExprBuilder scope st fs) -> IO () Source #

getPathCondition :: OnlineBackend solver scope st fs -> IO (Pred (ExprBuilder scope st fs)) Source #

collectAssumptions :: OnlineBackend solver scope st fs -> IO (Assumptions (ExprBuilder scope st fs)) Source #

addProofObligation :: OnlineBackend solver scope st fs -> Assertion (ExprBuilder scope st fs) -> IO () Source #

addDurableProofObligation :: OnlineBackend solver scope st fs -> Assertion (ExprBuilder scope st fs) -> IO () Source #

getProofObligations :: OnlineBackend solver scope st fs -> IO (ProofObligations (ExprBuilder scope st fs)) Source #

clearProofObligations :: OnlineBackend solver scope st fs -> IO () Source #

saveAssumptionState :: OnlineBackend solver scope st fs -> IO (AssumptionState (ExprBuilder scope st fs)) Source #

restoreAssumptionState :: OnlineBackend solver scope st fs -> AssumptionState (ExprBuilder scope st fs) -> IO () Source #

resetAssumptionState :: OnlineBackend solver scope st fs -> IO () Source #

class HasSymInterface sym bak | bak -> sym where Source #

Class for backend type that can retrieve sym values.

This is separate from IsSymBackend specifically to avoid the need for additional class constraints on the backendGetSym operation, which is occasionally useful.

Methods

backendGetSym :: bak -> sym Source #

Retrive the symbolic expression builder corresponding to this simulator backend.

Instances

Instances details
HasSymInterface (ExprBuilder t st fs) (SimpleBackend t st fs) Source # 
Instance details

Defined in Lang.Crucible.Backend.Simple

Methods

backendGetSym :: SimpleBackend t st fs -> ExprBuilder t st fs Source #

HasSymInterface (ExprBuilder t st fs) (OnlineBackend solver t st fs) Source # 
Instance details

Defined in Lang.Crucible.Backend.Online

Methods

backendGetSym :: OnlineBackend solver t st fs -> ExprBuilder t st fs Source #

data SomeBackend sym Source #

Constructors

forall bak.IsSymBackend sym bak => SomeBackend bak 

Assumption management

data CrucibleAssumption (e :: BaseType -> Type) Source #

This type describes assumptions made at some point during program execution.

Constructors

GenericAssumption ProgramLoc String (e BaseBoolType)

An unstructured description of the source of an assumption.

BranchCondition ProgramLoc (Maybe ProgramLoc) (e BaseBoolType)

This arose because we want to explore a specific path. The first location is the location of the branch predicate. The second one is the location of the branch target.

AssumingNoError SimError (e BaseBoolType)

An assumption justified by a proof of the impossibility of a certain simulator error.

data CrucibleEvent (e :: BaseType -> Type) where Source #

This type describes events we can track during program execution.

Constructors

CreateVariableEvent

This event describes the creation of a symbolic variable.

Fields

LocationReachedEvent :: ProgramLoc -> CrucibleEvent e

This event describes reaching a particular program location.

data CrucibleAssumptions (e :: BaseType -> Type) where Source #

This type tracks both logical assumptions and program events that are relevant when evaluating proof obligations arising from simulation.

concretizeEvents :: IsExpr e => (forall tp. e tp -> IO (GroundValue tp)) -> CrucibleAssumptions e -> IO [CrucibleEvent GroundValueWrapper] Source #

Given a ground evaluation function, compute a linear, ground-valued sequence of events corresponding to this program run.

ppEvent :: IsExpr e => CrucibleEvent e -> Doc ann Source #

Pretty print an event

trivialAssumption :: IsExpr e => CrucibleAssumption e -> Bool Source #

Check if an assumption is trivial (always true)

impossibleAssumption :: IsExpr e => CrucibleAssumption e -> Maybe AbortExecReason Source #

If an assumption is clearly impossible, return an abort reason that can be used to unwind the execution of this branch.

ppAssumption :: (forall tp. e tp -> Doc ann) -> CrucibleAssumption e -> Doc ann Source #

assumptionLoc :: CrucibleAssumption e -> ProgramLoc Source #

Return the program location associated with an assumption

eventLoc :: CrucibleEvent e -> ProgramLoc Source #

Return the program location associated with an event

mergeAssumptions :: IsExprBuilder sym => sym -> Pred sym -> Assumptions sym -> Assumptions sym -> IO (Assumptions sym) Source #

Merge the assumptions collected from the branches of a conditional.

assumptionPred :: CrucibleAssumption e -> e BaseBoolType Source #

Get the predicate associated with this assumption

assumptionsPred :: IsExprBuilder sym => sym -> Assumptions sym -> IO (Pred sym) Source #

Compute the logical predicate corresponding to this collection of assumptions.

flattenAssumptions :: IsExprBuilder sym => sym -> Assumptions sym -> IO [Assumption sym] Source #

Given a CrucibleAssumptions structure, flatten all the muxed assumptions into a flat sequence of assumptions that have been appropriately weakened. Note, once these assumptions have been flattened, their order might no longer strictly correspond to any concrete program run.

assumptionsTopLevelLocs :: CrucibleAssumptions e -> [ProgramLoc] Source #

Collect the program locations of all assumptions and events that did not occur in the context of a symbolic branch. These are locations that every program path represented by this CrucibleAssumptions structure must have passed through.

assert :: IsSymBackend sym bak => bak -> Pred sym -> SimErrorReason -> IO () Source #

Add a proof obligation using the current program location. Afterwards, assume the given fact.

Reexports

data LabeledPred pred msg #

Information about an assertion that was previously made.

Constructors

LabeledPred 

Fields

Instances

Instances details
Bifoldable LabeledPred 
Instance details

Defined in What4.LabeledPred

Methods

bifold :: Monoid m => LabeledPred m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> LabeledPred a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> LabeledPred a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> LabeledPred a b -> c #

Bifunctor LabeledPred 
Instance details

Defined in What4.LabeledPred

Methods

bimap :: (a -> b) -> (c -> d) -> LabeledPred a c -> LabeledPred b d #

first :: (a -> b) -> LabeledPred a c -> LabeledPred b c #

second :: (b -> c) -> LabeledPred a b -> LabeledPred a c #

Bitraversable LabeledPred 
Instance details

Defined in What4.LabeledPred

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> LabeledPred a b -> f (LabeledPred c d) #

Eq2 LabeledPred 
Instance details

Defined in What4.LabeledPred

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> LabeledPred a c -> LabeledPred b d -> Bool #

Ord2 LabeledPred 
Instance details

Defined in What4.LabeledPred

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> LabeledPred a c -> LabeledPred b d -> Ordering #

Show2 LabeledPred 
Instance details

Defined in What4.LabeledPred

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> LabeledPred a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [LabeledPred a b] -> ShowS #

Generic1 (LabeledPred pred :: Type -> Type) 
Instance details

Defined in What4.LabeledPred

Associated Types

type Rep1 (LabeledPred pred) :: k -> Type #

Methods

from1 :: forall (a :: k). LabeledPred pred a -> Rep1 (LabeledPred pred) a #

to1 :: forall (a :: k). Rep1 (LabeledPred pred) a -> LabeledPred pred a #

Foldable (LabeledPred pred) 
Instance details

Defined in What4.LabeledPred

Methods

fold :: Monoid m => LabeledPred pred m -> m #

foldMap :: Monoid m => (a -> m) -> LabeledPred pred a -> m #

foldMap' :: Monoid m => (a -> m) -> LabeledPred pred a -> m #

foldr :: (a -> b -> b) -> b -> LabeledPred pred a -> b #

foldr' :: (a -> b -> b) -> b -> LabeledPred pred a -> b #

foldl :: (b -> a -> b) -> b -> LabeledPred pred a -> b #

foldl' :: (b -> a -> b) -> b -> LabeledPred pred a -> b #

foldr1 :: (a -> a -> a) -> LabeledPred pred a -> a #

foldl1 :: (a -> a -> a) -> LabeledPred pred a -> a #

toList :: LabeledPred pred a -> [a] #

null :: LabeledPred pred a -> Bool #

length :: LabeledPred pred a -> Int #

elem :: Eq a => a -> LabeledPred pred a -> Bool #

maximum :: Ord a => LabeledPred pred a -> a #

minimum :: Ord a => LabeledPred pred a -> a #

sum :: Num a => LabeledPred pred a -> a #

product :: Num a => LabeledPred pred a -> a #

Eq pred => Eq1 (LabeledPred pred) 
Instance details

Defined in What4.LabeledPred

Methods

liftEq :: (a -> b -> Bool) -> LabeledPred pred a -> LabeledPred pred b -> Bool #

Ord pred => Ord1 (LabeledPred pred) 
Instance details

Defined in What4.LabeledPred

Methods

liftCompare :: (a -> b -> Ordering) -> LabeledPred pred a -> LabeledPred pred b -> Ordering #

Show pred => Show1 (LabeledPred pred) 
Instance details

Defined in What4.LabeledPred

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> LabeledPred pred a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [LabeledPred pred a] -> ShowS #

Traversable (LabeledPred pred) 
Instance details

Defined in What4.LabeledPred

Methods

traverse :: Applicative f => (a -> f b) -> LabeledPred pred a -> f (LabeledPred pred b) #

sequenceA :: Applicative f => LabeledPred pred (f a) -> f (LabeledPred pred a) #

mapM :: Monad m => (a -> m b) -> LabeledPred pred a -> m (LabeledPred pred b) #

sequence :: Monad m => LabeledPred pred (m a) -> m (LabeledPred pred a) #

Functor (LabeledPred pred) 
Instance details

Defined in What4.LabeledPred

Methods

fmap :: (a -> b) -> LabeledPred pred a -> LabeledPred pred b #

(<$) :: a -> LabeledPred pred b -> LabeledPred pred a #

(Data pred, Data msg) => Data (LabeledPred pred msg) 
Instance details

Defined in What4.LabeledPred

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LabeledPred pred msg -> c (LabeledPred pred msg) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (LabeledPred pred msg) #

toConstr :: LabeledPred pred msg -> Constr #

dataTypeOf :: LabeledPred pred msg -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (LabeledPred pred msg)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (LabeledPred pred msg)) #

gmapT :: (forall b. Data b => b -> b) -> LabeledPred pred msg -> LabeledPred pred msg #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LabeledPred pred msg -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LabeledPred pred msg -> r #

gmapQ :: (forall d. Data d => d -> u) -> LabeledPred pred msg -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LabeledPred pred msg -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LabeledPred pred msg -> m (LabeledPred pred msg) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LabeledPred pred msg -> m (LabeledPred pred msg) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LabeledPred pred msg -> m (LabeledPred pred msg) #

Generic (LabeledPred pred msg) 
Instance details

Defined in What4.LabeledPred

Associated Types

type Rep (LabeledPred pred msg) :: Type -> Type #

Methods

from :: LabeledPred pred msg -> Rep (LabeledPred pred msg) x #

to :: Rep (LabeledPred pred msg) x -> LabeledPred pred msg #

(Show pred, Show msg) => Show (LabeledPred pred msg) 
Instance details

Defined in What4.LabeledPred

Methods

showsPrec :: Int -> LabeledPred pred msg -> ShowS #

show :: LabeledPred pred msg -> String #

showList :: [LabeledPred pred msg] -> ShowS #

(Eq pred, Eq msg) => Eq (LabeledPred pred msg) 
Instance details

Defined in What4.LabeledPred

Methods

(==) :: LabeledPred pred msg -> LabeledPred pred msg -> Bool #

(/=) :: LabeledPred pred msg -> LabeledPred pred msg -> Bool #

(Ord pred, Ord msg) => Ord (LabeledPred pred msg) 
Instance details

Defined in What4.LabeledPred

Methods

compare :: LabeledPred pred msg -> LabeledPred pred msg -> Ordering #

(<) :: LabeledPred pred msg -> LabeledPred pred msg -> Bool #

(<=) :: LabeledPred pred msg -> LabeledPred pred msg -> Bool #

(>) :: LabeledPred pred msg -> LabeledPred pred msg -> Bool #

(>=) :: LabeledPred pred msg -> LabeledPred pred msg -> Bool #

max :: LabeledPred pred msg -> LabeledPred pred msg -> LabeledPred pred msg #

min :: LabeledPred pred msg -> LabeledPred pred msg -> LabeledPred pred msg #

type Rep1 (LabeledPred pred :: Type -> Type) 
Instance details

Defined in What4.LabeledPred

type Rep1 (LabeledPred pred :: Type -> Type) = D1 ('MetaData "LabeledPred" "What4.LabeledPred" "what4-1.5.1-6GimHtONvd1LMJIg4FyjIh" 'False) (C1 ('MetaCons "LabeledPred" 'PrefixI 'True) (S1 ('MetaSel ('Just "_labeledPred") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 pred) :*: S1 ('MetaSel ('Just "_labeledPredMsg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1))
type Rep (LabeledPred pred msg) 
Instance details

Defined in What4.LabeledPred

type Rep (LabeledPred pred msg) = D1 ('MetaData "LabeledPred" "What4.LabeledPred" "what4-1.5.1-6GimHtONvd1LMJIg4FyjIh" 'False) (C1 ('MetaCons "LabeledPred" 'PrefixI 'True) (S1 ('MetaSel ('Just "_labeledPred") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 pred) :*: S1 ('MetaSel ('Just "_labeledPredMsg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 msg)))

labeledPred :: forall pred msg pred' f. Functor f => (pred -> f pred') -> LabeledPred pred msg -> f (LabeledPred pred' msg) #

Predicate that was asserted.

labeledPredMsg :: forall pred msg msg' f. Functor f => (msg -> f msg') -> LabeledPred pred msg -> f (LabeledPred pred msg') #

Message added when assumption/assertion was made.

data AssumptionStack asmp ast Source #

An assumption stack is a data structure for tracking logical assumptions and proof obligations. Assumptions can be added to the current stack frame, and stack frames may be pushed (to remember a previous state) or popped to restore a previous state.

data FrameIdentifier Source #

A FrameIdentifier is a value that identifies an an assumption frame. These are expected to be unique when a new frame is pushed onto the stack. This is primarily a debugging aid, to ensure that stack management remains well-bracketed.

data ProofGoal asmp goal Source #

A proof goal consists of a collection of assumptions that were in scope when an assertion was made, together with the given assertion.

Constructors

ProofGoal 

Fields

data Goals asmp goal Source #

A collection of goals, which can represent shared assumptions.

Constructors

Assuming asmp !(Goals asmp goal)

Make an assumption that is in context for all the contained goals.

Prove goal

A proof obligation, to be proved in the context of all previously-made assumptions.

ProveConj !(Goals asmp goal) !(Goals asmp goal)

A conjunction of two goals.

Instances

Instances details
(Show asmp, Show goal) => Show (Goals asmp goal) Source # 
Instance details

Defined in Lang.Crucible.Backend.ProofGoals

Methods

showsPrec :: Int -> Goals asmp goal -> ShowS #

show :: Goals asmp goal -> String #

showList :: [Goals asmp goal] -> ShowS #

goalsToList :: Monoid asmp => Goals asmp goal -> [ProofGoal asmp goal] Source #

Render the tree of goals as a list instead, duplicating shared assumptions over each goal as necessary.

Aborting execution

data AbortExecReason Source #

This is used to signal that current execution path is infeasible.

Constructors

InfeasibleBranch ProgramLoc

We have discovered that the currently-executing branch is infeasible. The given program location describes the point at which infeasibility was discovered.

AssertionFailure SimError

An assertion concretely failed.

VariantOptionsExhausted ProgramLoc

We tried all possible cases for a variant, and now we should do something else.

EarlyExit ProgramLoc

We invoked a function which ends the current thread of execution (e.g., abort() or exit(1)).

abortExecBecause :: AbortExecReason -> IO a Source #

Throw an exception, thus aborting the current execution path.

Utilities

addAssertion :: IsSymBackend sym bak => bak -> Assertion sym -> IO () Source #

Add a proof obligation for the given predicate, and then assume it (when the assertThenAssume option is true). Note that assuming the prediate might cause the current execution path to abort, if we happened to assume something that is obviously false.

addDurableAssertion :: IsSymBackend sym bak => bak -> Assertion sym -> IO () Source #

Add a durable proof obligation for the given predicate, and then assume it (when the assertThenAssume option is true). Note that assuming the prediate might cause the current execution path to abort, if we happened to assume something that is obviously false.

addAssertionM :: IsSymBackend sym bak => bak -> IO (Pred sym) -> SimErrorReason -> IO () Source #

Run the given action to compute a predicate, and assert it.

addFailedAssertion :: IsSymBackend sym bak => bak -> SimErrorReason -> IO a Source #

Add a proof obligation for False. This always aborts execution of the current path, because after asserting false, we get to assume it, and so there is no need to check anything after. This is why the resulting IO computation can have the fully polymorphic type.

assertIsInteger :: IsSymBackend sym bak => bak -> SymReal sym -> SimErrorReason -> IO () Source #

Assert that the given real-valued expression is an integer.

readPartExpr :: IsSymBackend sym bak => bak -> PartExpr (Pred sym) v -> SimErrorReason -> IO v Source #

Given a partial expression, assert that it is defined and return the underlying value.