crucible-llvm-0.6: Support for translating and executing LLVM code in Crucible
Copyright(c) Galois Inc 2018
LicenseBSD3
MaintainerLangston Barrett <lbarrett@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.LLVM.Errors.MemoryError

Description

 
Synopsis

Documentation

data MemoryError sym where Source #

Constructors

MemoryError :: 1 <= w => MemoryOp sym w -> MemoryErrorReason -> MemoryError sym 

type MemErrContext sym w = MemoryOp sym w Source #

explain :: IsExpr (SymExpr sym) => MemoryError sym -> Doc ann Source #

details :: IsExpr (SymExpr sym) => MemoryError sym -> Doc ann Source #

data MemoryOp sym w Source #

Constructors

MemLoadOp StorageType (Maybe String) (LLVMPtr sym w) (Mem sym) 
MemStoreOp StorageType (Maybe String) (LLVMPtr sym w) (Mem sym) 
MemStoreBytesOp (Maybe String) (LLVMPtr sym w) (Maybe (SymBV sym w)) (Mem sym) 
forall wlen.1 <= wlen => MemCopyOp (Maybe String, LLVMPtr sym w) (Maybe String, LLVMPtr sym w) (SymBV sym wlen) (Mem sym) 
MemLoadHandleOp (Maybe Type) (Maybe String) (LLVMPtr sym w) (Mem sym) 
forall wlen.1 <= wlen => MemInvalidateOp Text (Maybe String) (LLVMPtr sym w) (SymBV sym wlen) (Mem sym) 

memOpMem :: MemoryOp sym w -> Mem sym Source #

ppMemoryOp :: IsExpr (SymExpr sym) => MemoryOp sym w -> Doc ann Source #

concMemoryError :: IsExprBuilder sym => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> MemoryError sym -> IO (MemoryError sym) Source #

concMemoryOp :: (1 <= w, IsExprBuilder sym) => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> MemoryOp sym w -> IO (MemoryOp sym w) Source #