SSTG-0.1.1.3: STG Symbolic Execution

Safe HaskellSafe
LanguageHaskell2010

SSTG.Core.Language.Support

Description

Symbolic STG Execution Support Architecture

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 #

fmap :: Functor f => forall a b. (a -> b) -> f a -> f b #

pure :: Applicative f => forall a. a -> f a #

Lift a value.

(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b #

Sequential application.

return :: Monad m => forall a. a -> m a #

Inject a value into the monadic type.

(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

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 Stack Source #

Execution stack used in graph reduction semnatics.

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 

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.

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

data Code Source #

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

data PathCons Source #

Path constraints are the conjunctive normal form of Constraints.

data Constraint Source #

Constraints denote logical paths taken in program execution thus far.

Constructors

Constraint (AltCon, [Var]) Expr Locals Bool 

nameOccStr :: Name -> String Source #

A Name's occurrence string.

varName :: Var -> Name Source #

Variable name.

incStatusSteps :: Status -> Status Source #

Increment Status steps.

updateStatusId :: Int -> Status -> Status Source #

Update the Status id.

empty_stack :: Stack Source #

Empty `Stack.

stackToList :: Stack -> [Frame] Source #

Stack as list of Frames.

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

List insertion into Locals.

localsToList :: Locals -> [(Name, Value)] Source #

Locals to key value pairs.

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.

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

Heap to key value pairs.

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.

globalsToList :: Globals -> [(Name, Value)] Source #

Globals to key value pairs.

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.