SSTG-0.1.0.6: STG Symbolic Execution

Safe HaskellSafe
LanguageHaskell2010

SSTG.Core.Execution.Models

Description

Symbolic STG Execution Models

Synopsis

Documentation

newtype SymbolicT s a Source #

Symbolic Transformation represents transformations applied to some State`(s). This is useful in allowing us to transfer from different actions within the engine.

Constructors

SymbolicT 

Fields

  • run :: s -> (s, a)
     

Instances

Monad (SymbolicT s) Source #

Monad instance of Symbolic Transformation.

Methods

(>>=) :: SymbolicT s a -> (a -> SymbolicT s b) -> SymbolicT s b #

(>>) :: SymbolicT s a -> SymbolicT s b -> SymbolicT s b #

return :: a -> SymbolicT s a #

fail :: String -> SymbolicT s a #

Functor (SymbolicT s) Source #

Functor instance of Symbolic Transformation.

Methods

fmap :: (a -> b) -> SymbolicT s a -> SymbolicT s b #

(<$) :: a -> SymbolicT s b -> SymbolicT s a #

Applicative (SymbolicT s) Source #

Applicative instance of Symbolic Transformation.

Methods

pure :: a -> SymbolicT s a #

(<*>) :: SymbolicT s (a -> b) -> SymbolicT s a -> SymbolicT s b #

(*>) :: SymbolicT s a -> SymbolicT s b -> SymbolicT s b #

(<*) :: SymbolicT s a -> SymbolicT s b -> SymbolicT s a #

data State Source #

State contains the information necessary to perform symbolic execution. Eval/Apply graph reduction semantics are used.

data Symbol Source #

Symbolic variables. The Maybe (Expr, Locals) can be used to trace the source from which the symbolic variable was generated. For instance, this is useful during symbolic function application.

Constructors

Symbol Var (Maybe (Expr, Locals)) 

data Status Source #

State status.

Constructors

Status 

Fields

newtype Stack Source #

Execution stack used in graph reduction semnatics.

Constructors

Stack [Frame] 

data Value Source #

A Value is something that we aim to reduce our current expression down into. MemAddr is a pointer to an object on the heap, such as FunObj or ConObj, which are "returned" from expression evaluation in this form.

Constructors

LitVal Lit 
MemVal MemAddr 

newtype Locals Source #

Locals binds a Var's Name to its some Value.

Constructors

Locals (Map Name Value) 

data Heap Source #

Heaps map MemAddr to HeapObj, while keeping track of the last address that was allocated. This allows us to consistently allocate fresh addresses on the Heap.

Constructors

Heap (Map MemAddr HeapObj) MemAddr 

newtype Globals Source #

Globals are statically loaded at the time when a State is loaded. However, because uninterpreted / out-of-scope variables are made symbolic at runtime, it can be modified during execution.

Constructors

Globals (Map Name Value) 

data Code Source #

Evaluation of the current expression. We are either evaluating, or ready to return with some Value.

type PathCons = [PathCond] Source #

Path constraints.

data PathCond Source #

Path conditions denote logical paths taken in program execution thus far.

Constructors

PathCond (AltCon, [Var]) Expr Locals Bool 

newtype SymLinks Source #

Symbolic link tables helps keep track of what names went to what, what?

Constructors

SymLinks (Map Name Name) 

nameOccStr :: Name -> String Source #

A Name's occurrence string.

nameUnique :: Name -> Int Source #

Name's unique Int key.

varName :: Var -> Name Source #

Variable name.

insertLocalsList :: [(Var, Value)] -> Locals -> Locals Source #

List insertion into Locals.

allocHeap :: HeapObj -> Heap -> (Heap, MemAddr) Source #

Heap allocation. Updates the last MemAddr kept in the Heap.

allocHeapList :: [HeapObj] -> Heap -> (Heap, [MemAddr]) Source #

Allocate a list of HeapObj in a Heap, returning in the same order the MemAddr at which they have been allocated at.

insertHeap :: MemAddr -> HeapObj -> Heap -> Heap Source #

Heap direct insertion at a specific MemAddr.

insertHeapList :: [(MemAddr, HeapObj)] -> Heap -> Heap Source #

Insert a list of HeapObj at specified MemAddr locations.

insertGlobalsList :: [(Var, Value)] -> Globals -> Globals Source #

Insert a list of Var and Value pairs into Globals. This would typically occur for new symbolic variables created from uninterpreted / out-of-scope variables during runtime.

lookupValue :: Var -> Locals -> Globals -> Maybe Value Source #

Value lookup from the Locals first, then Globals.

vlookupHeap :: Var -> Locals -> Globals -> Heap -> Maybe (MemAddr, HeapObj) Source #

Heap lookup. Returns the corresponding MemAddr and HeapObj if found.

memAddrType :: MemAddr -> Heap -> Maybe Type Source #

Type of HeapObj held at MemAddr, if found.