crucible-llvm-0.6: Support for translating and executing LLVM code in Crucible
Copyright(c) Galois Inc 2011-2020
LicenseBSD3
MaintainerRob Dockins <rdockins@galois.com>
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.LLVM.MemModel.MemLog

Description

 
Synopsis

Allocation logs

data AllocInfo sym Source #

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.

Constructors

forall w.1 <= w => AllocInfo AllocType (Maybe (SymBV sym w)) Mutability Alignment String 

newtype MemAllocs sym Source #

A record of which memory regions have been allocated or freed.

Constructors

MemAllocs [MemAlloc sym] 

Instances

Instances details
Monoid (MemAllocs sym) Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemModel.MemLog

Methods

mempty :: MemAllocs sym #

mappend :: MemAllocs sym -> MemAllocs sym -> MemAllocs sym #

mconcat :: [MemAllocs sym] -> MemAllocs sym #

Semigroup (MemAllocs sym) Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemModel.MemLog

Methods

(<>) :: MemAllocs sym -> MemAllocs sym -> MemAllocs sym #

sconcat :: NonEmpty (MemAllocs sym) -> MemAllocs sym #

stimes :: Integral b => b -> MemAllocs sym -> MemAllocs sym #

data MemAlloc sym Source #

Stores writeable memory allocations.

Constructors

Allocations (Map Natural (AllocInfo sym))

A collection of consecutive basic allocations.

MemFree (SymNat sym) String

Freeing of the given block ID.

AllocMerge (Pred sym) (MemAllocs sym) (MemAllocs sym)

The merger of two allocations.

sizeMemAllocs :: MemAllocs sym -> Int Source #

Compute the size of a MemAllocs log.

allocMemAllocs :: Natural -> AllocInfo sym -> MemAllocs sym -> MemAllocs sym Source #

Allocate a new block with the given allocation ID.

freeMemAllocs Source #

Arguments

:: SymNat sym 
-> String

Location info for debugging

-> MemAllocs sym 
-> MemAllocs sym 

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 #

Look up the AllocInfo for the given allocation number. A Just result indicates that the specified memory region may or may not still be allocated; Nothing indicates that the memory region is definitely not allocated.

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)

MemCopy src len copies len bytes from [src..src+len).

MemSet (SymBV sym 8) (SymBV sym w)

MemSet val len fills the destination with len copies of byte val.

MemStore (LLVMVal sym) StorageType Alignment

MemStore val ty al writes value val with type ty at the destination. with alignment at least al.

MemArrayStore (SymArray sym (SingleCtx (BaseBVType w)) (BaseBVType 8)) (Maybe (SymBV sym w))

MemArrayStore block (Just len) writes byte-array block of size len at the destination; MemArrayStore block Nothing writes byte-array block of unbounded size

MemInvalidate Text (SymBV sym w)

MemInvalidate len flags len bytes as uninitialized.

data MemWrite sym Source #

Constructors

forall w.1 <= w => MemWrite (LLVMPtr sym w) (WriteSource sym w)

MemWrite dst src represents a write to dst from the given source.

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] 

Instances

Instances details
Monoid (MemWrites sym) Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemModel.MemLog

Methods

mempty :: MemWrites sym #

mappend :: MemWrites sym -> MemWrites sym -> MemWrites sym #

mconcat :: [MemWrites sym] -> MemWrites sym #

Semigroup (MemWrites sym) Source # 
Instance details

Defined in Lang.Crucible.LLVM.MemModel.MemLog

Methods

(<>) :: MemWrites sym -> MemWrites sym -> MemWrites sym #

sconcat :: NonEmpty (MemWrites sym) -> MemWrites sym #

stimes :: Integral b => b -> MemWrites sym -> MemWrites 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.

memWritesSingleton :: (IsExprBuilder sym, 1 <= w) => LLVMPtr sym w -> WriteSource sym w -> MemWrites sym Source #

Memory logs

data MemState sym Source #

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 #

data Mem 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 

Pretty printing

ppType :: StorageType -> Doc ann Source #

Pretty print type.

ppPtr :: IsExpr (SymExpr sym) => LLVMPtr sym wptr -> Doc ann Source #

ppAllocs :: IsExpr (SymExpr sym) => MemAllocs sym -> Doc ann Source #

ppMem :: IsExpr (SymExpr sym) => Mem sym -> Doc ann Source #

ppMemWrites :: IsExpr (SymExpr sym) => MemWrites sym -> Doc ann Source #

ppWrite :: IsExpr (SymExpr sym) => MemWrite sym -> Doc ann Source #

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 #