shivers-cfg-0.1.1: Implementation of Shivers' Control-Flow Analysis

Safe HaskellNone
LanguageHaskell98

AbsCF

Contents

Description

This module calculates an abstract control graph by evaluating a CPSScheme program, following the definitions in Olin Shivers' "Control-Flow Analysis of Higher-Order Languages".

Synopsis

Types

type Closure c = (Lambda, BEnv c) Source

A closure is a lambda expression bound to a binding environment

class (Show c, Eq c, Ord c) => Contour c where Source

The abstract semantics are parametrized by a (finite) set of contours. Here, this is modeled via a type class.

Methods

initial Source

Arguments

:: c

The initial contour, used by evalCPS, but not used

nb Source

Arguments

:: c 
-> Label 
-> c

Generating a new contour. This method has access to the label of the current call site, in case it wants to record this information.

newtype CFA0 Source

A possible contour set, the singleton set. Shivers calls this 0CFA, but in Haskell, types and constructor names have to start with an upper case letter.

Constructors

CFA0 () 

newtype CFA1 Source

A more detailed contour set, remembering the call site.

Constructors

CFA1 Label 

type BEnv c = Label :⇀ c Source

A binding environment maps the labels of Lambda and Let bindings to the innermost contour generated for these expressions

type VEnv c = (Var c) :⇀ D c Source

A variable environment maps variable names together with a contour to a value. The second parameter is required to allow for different, shadowed bindings of the same variable to coexist.

data Proc c Source

Here, we do not care about values any more, only about procedures:

Constructors

PC (Closure c)

A closed lambda expression

PP Prim

A primitive operation

Stop 

Instances

Eq c => Eq (Proc c) Source 
Ord c => Ord (Proc c) Source 
Show c => Show (Proc c) Source 

type D c = [Proc c] Source

For variables, we only remember the set of possible program values. We use a list here instead of a set for the more convenient sytanx (list comprehension etc.).

type CCtxt c = Label BEnv c Source

The origin of an edge in the control graph is a call position bundled with the binding environment at that point.

type CCache c = CCtxt c :⇀ D c Source

The resulting control flow graph has edges from call sites (annotated by the current binding environment) to functions (e.g. lambdas with closure, primitive operations, or Stop)

type Ans c = CCache c Source

The result of evaluating a program is an approximation to the control flow graph.

type FState c = (Proc c, [D c], VEnv c, c) Source

The uncurried arguments of evalF

type CState c = (Call, BEnv c, VEnv c, c) Source

The uncurried arguments of evalC

type Memo c = Set (Either (FState c) (CState c)) Source

We need memoization. This Data structure is used to remember all visited arguments

Evaluation functions

evalCPS :: Contour c => Prog -> Ans c Source

evalCPS evaluates a whole program, by initializing the envirnoments and passing the Stop continuation to the outermost lambda

evalCPS_CFA0 :: Prog -> Ans CFA0 Source

Variants fixing the coutour

evalV :: Contour c => Val -> BEnv c -> VEnv c -> D c Source

evalC (called A by Shivers) evaluates a syntactical value to a semantical piece of data.

evalF :: Contour c => FState c -> State (Memo c) (Ans c) Source

evalF evaluates a function call, distinguishing between lambda expressions, primitive operations and the special Stop continuation. It calles evalC for the function bodies.

Because we want to memoize the results of the recursive calls, and do not want to separate that code, the that to be

evalC :: Contour c => CState c -> State (Memo c) (Ans c) Source

evalC evaluates the body of a function, which can either be an application (which is then evaluated using evalF) or a Let statement.

graphToEdgelist :: Show c => Ans c -> [Label Label] Source

For the visualization, we need a list of edges from Label to Label. TODO: Handle STOP