Copyright | (c) Galois Inc 2011-2020 |
---|---|
License | BSD3 |
Maintainer | Rob Dockins <[email protected]> |
Stability | provisional |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Lang.Crucible.LLVM.MemModel.MemLog
Description
Synopsis
- data AllocType
- data Mutability
- data AllocInfo sym = forall w.1 <= w => AllocInfo AllocType (Maybe (SymBV sym w)) Mutability Alignment String
- newtype MemAllocs sym = MemAllocs [MemAlloc sym]
- data MemAlloc sym
- sizeMemAllocs :: MemAllocs sym -> Int
- allocMemAllocs :: Natural -> AllocInfo sym -> MemAllocs sym -> MemAllocs sym
- freeMemAllocs :: SymNat sym -> String -> MemAllocs sym -> MemAllocs sym
- muxMemAllocs :: IsExpr (SymExpr sym) => Pred sym -> MemAllocs sym -> MemAllocs sym -> MemAllocs sym
- popMemAllocs :: forall sym. MemAllocs sym -> MemAllocs sym
- possibleAllocInfo :: forall sym. IsExpr (SymExpr sym) => Natural -> MemAllocs sym -> Maybe (AllocInfo sym)
- isAllocatedGeneric :: forall sym. (IsExpr (SymExpr sym), IsExprBuilder sym) => sym -> (AllocInfo sym -> IO (Pred sym)) -> SymNat sym -> MemAllocs sym -> IO (Pred sym, Pred sym)
- data WriteSource sym w
- = MemCopy (LLVMPtr sym w) (SymBV sym w)
- | MemSet (SymBV sym 8) (SymBV sym w)
- | MemStore (LLVMVal sym) StorageType Alignment
- | MemArrayStore (SymArray sym (SingleCtx (BaseBVType w)) (BaseBVType 8)) (Maybe (SymBV sym w))
- | MemInvalidate Text (SymBV sym w)
- data MemWrite sym
- = forall w.1 <= w => MemWrite (LLVMPtr sym w) (WriteSource sym w)
- | WriteMerge (Pred sym) (MemWrites sym) (MemWrites sym)
- newtype MemWrites sym = MemWrites [MemWritesChunk sym]
- data MemWritesChunk sym
- = MemWritesChunkFlat [MemWrite sym]
- | MemWritesChunkIndexed (IntMap [MemWrite sym])
- memWritesSingleton :: (IsExprBuilder sym, 1 <= w) => LLVMPtr sym w -> WriteSource sym w -> MemWrites sym
- data MemState sym
- = EmptyMem !Int !Int (MemChanges sym)
- | StackFrame !Int !Int Text (MemChanges sym) (MemState sym)
- | BranchFrame !Int !Int (MemChanges sym) (MemState sym)
- type MemChanges sym = (MemAllocs sym, MemWrites sym)
- memState :: Lens' (Mem sym) (MemState sym)
- data Mem sym = Mem {
- memEndianForm :: EndianForm
- _memState :: MemState sym
- emptyChanges :: MemChanges sym
- emptyMem :: EndianForm -> Mem sym
- memEndian :: Mem sym -> EndianForm
- ppType :: StorageType -> Doc ann
- ppPtr :: IsExpr (SymExpr sym) => LLVMPtr sym wptr -> Doc ann
- ppAllocInfo :: IsExpr (SymExpr sym) => (Natural, AllocInfo sym) -> Doc ann
- ppAllocs :: IsExpr (SymExpr sym) => MemAllocs sym -> Doc ann
- ppMem :: IsExpr (SymExpr sym) => Mem sym -> Doc ann
- ppMemWrites :: IsExpr (SymExpr sym) => MemWrites sym -> Doc ann
- ppWrite :: IsExpr (SymExpr sym) => MemWrite sym -> Doc ann
- writeRangesMem :: (IsExprBuilder sym, HasPtrWidth w) => sym -> Mem sym -> MaybeT IO (Map Natural [(SymBV sym w, SymBV sym w)])
- concPtr :: (IsExprBuilder sym, 1 <= w) => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> RegValue sym (LLVMPointerType w) -> IO (RegValue sym (LLVMPointerType w))
- concLLVMVal :: IsExprBuilder sym => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> LLVMVal sym -> IO (LLVMVal sym)
- concMem :: IsExprBuilder sym => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> Mem sym -> IO (Mem sym)
Allocation logs
Constructors
StackAlloc | |
HeapAlloc | |
GlobalAlloc |
Instances
Show AllocType Source # | |
Eq AllocType Source # | |
Ord AllocType Source # | |
Defined in Lang.Crucible.LLVM.MemModel.MemLog |
data Mutability Source #
Instances
Show Mutability Source # | |
Defined in Lang.Crucible.LLVM.MemModel.MemLog Methods showsPrec :: Int -> Mutability -> ShowS # show :: Mutability -> String # showList :: [Mutability] -> ShowS # | |
Eq Mutability Source # | |
Defined in Lang.Crucible.LLVM.MemModel.MemLog | |
Ord Mutability Source # | |
Defined in Lang.Crucible.LLVM.MemModel.MemLog Methods compare :: Mutability -> Mutability -> Ordering # (<) :: Mutability -> Mutability -> Bool # (<=) :: Mutability -> Mutability -> Bool # (>) :: Mutability -> Mutability -> Bool # (>=) :: Mutability -> Mutability -> Bool # max :: Mutability -> Mutability -> Mutability # min :: Mutability -> Mutability -> Mutability # |
Details of a single allocation. The Maybe SymBV
argument is either a
size or Nothing
representing an unbounded allocation. The Mutability
indicates whether the region is read-only. The String
contains source
location information for use in error messages.
newtype MemAllocs sym Source #
A record of which memory regions have been allocated or freed.
Stores writeable memory allocations.
allocMemAllocs :: Natural -> AllocInfo sym -> MemAllocs sym -> MemAllocs sym Source #
Allocate a new block with the given allocation ID.
Free the block with the given allocation ID.
muxMemAllocs :: IsExpr (SymExpr sym) => Pred sym -> MemAllocs sym -> MemAllocs sym -> MemAllocs sym Source #
popMemAllocs :: forall sym. MemAllocs sym -> MemAllocs sym Source #
Purge all stack allocations from the allocation log.
possibleAllocInfo :: forall sym. IsExpr (SymExpr sym) => Natural -> MemAllocs sym -> Maybe (AllocInfo sym) Source #
isAllocatedGeneric :: forall sym. (IsExpr (SymExpr sym), IsExprBuilder sym) => sym -> (AllocInfo sym -> IO (Pred sym)) -> SymNat sym -> MemAllocs sym -> IO (Pred sym, Pred sym) Source #
Generalized function for checking whether a memory region ID is allocated.
The first predicate indicates whether the region was allocated, the second indicates whether it has *not* been freed.
Write logs
data WriteSource sym w Source #
Constructors
MemCopy (LLVMPtr sym w) (SymBV sym w) |
|
MemSet (SymBV sym 8) (SymBV sym w) |
|
MemStore (LLVMVal sym) StorageType Alignment |
|
MemArrayStore (SymArray sym (SingleCtx (BaseBVType w)) (BaseBVType 8)) (Maybe (SymBV sym w)) |
|
MemInvalidate Text (SymBV sym w) |
|
Constructors
forall w.1 <= w => MemWrite (LLVMPtr sym w) (WriteSource sym w) |
|
WriteMerge (Pred sym) (MemWrites sym) (MemWrites sym) | The merger of two memories. |
newtype MemWrites sym Source #
Memory writes are represented as a list of chunks of writes. Chunks alternate between being indexed and being flat.
Constructors
MemWrites [MemWritesChunk sym] |
data MemWritesChunk sym Source #
A chunk of memory writes is either indexed or flat (unindexed). An indexed chunk consists of writes to addresses with concrete base pointers and is represented as a map. A flat chunk consists of writes to addresses with symbolic base pointers. A merge of two indexed chunks is a indexed chunk, while any other merge is part of a flat chunk.
Constructors
MemWritesChunkFlat [MemWrite sym] | |
MemWritesChunkIndexed (IntMap [MemWrite sym]) |
memWritesSingleton :: (IsExprBuilder sym, 1 <= w) => LLVMPtr sym w -> WriteSource sym w -> MemWrites sym Source #
Memory logs
A state of memory as of a stack push, branch, or merge. Counts of the total number of allocations and writes are kept for performance metrics.
Constructors
EmptyMem !Int !Int (MemChanges sym) | Represents initial memory and changes since then. Changes are stored in order, with more recent changes closer to the head of the list. |
StackFrame !Int !Int Text (MemChanges sym) (MemState sym) | Represents a push of a stack frame, and changes since that stack push. The text value gives a user-consumable name for the stack frame. Changes are stored in order, with more recent changes closer to the head of the list. |
BranchFrame !Int !Int (MemChanges sym) (MemState sym) | Represents a push of a branch frame, and changes since that branch. Changes are stored in order, with more recent changes closer to the head of the list. |
type MemChanges sym = (MemAllocs sym, MemWrites sym) Source #
A symbolic representation of the LLVM heap.
This representation is designed to support a variety of operations including reads and writes of symbolic data to symbolic addresses, symbolic memcpy and memset, and merging two memories in a single memory using an if-then-else operation.
A common use case is that the symbolic simulator will branch into
two execution states based on a symbolic branch, make different
memory modifications on each branch, and then need to merge the two
memories to resume execution along a single path using the branch
condition. To support this, our memory representation supports
"branch frames", at any point one can insert a fresh branch frame
(see branchMem
), and then at some later point merge two memories
back into a single memory (see mergeMem
). Our mergeMem
implementation is able to efficiently merge memories, but requires
that one only merge memories that were identical prior to the last
branch.
Constructors
Mem | |
Fields
|
emptyChanges :: MemChanges sym Source #
emptyMem :: EndianForm -> Mem sym Source #
memEndian :: Mem sym -> EndianForm Source #
Pretty printing
ppType :: StorageType -> Doc ann Source #
Pretty print type.
Write ranges
writeRangesMem :: (IsExprBuilder sym, HasPtrWidth w) => sym -> Mem sym -> MaybeT IO (Map Natural [(SymBV sym w, SymBV sym w)]) Source #
Compute the ranges (pairs of the form pointer offset and size) for all memory writes, indexed by the pointer base. The result is Nothing if the memory contains any writes with symbolic pointer base, or without size.
Concretization
concPtr :: (IsExprBuilder sym, 1 <= w) => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> RegValue sym (LLVMPointerType w) -> IO (RegValue sym (LLVMPointerType w)) Source #
concLLVMVal :: IsExprBuilder sym => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> LLVMVal sym -> IO (LLVMVal sym) Source #
concMem :: IsExprBuilder sym => sym -> (forall tp. SymExpr sym tp -> IO (GroundValue tp)) -> Mem sym -> IO (Mem sym) Source #