| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Tokstyle.Analysis.Types
Synopsis
- type CallGraph = Map FunctionName CalleeMap
- data CallSite = CallSite {
- csNodeId :: NodeId
- csCallType :: CallType
- data CallType
- type FunctionName = Text
- type CalleeMap = Map FunctionName (Set CallSite)
- type PointsToMap = Map AbstractLocation (Set AbstractLocation)
- type PointsToSummary = Map Context PointsToSummaryData
- data PointsToSummaryData = PointsToSummaryData {}
- getCallers :: CallGraph -> FunctionName -> Map FunctionName (Set CallSite)
- data AbstractLocation
- toAbstractLocation :: HasCallStack => Node (Lexeme Text) -> AbstractLocation
- type NodeId = Int
- type Context = [NodeId]
- lookupOrError :: (Ord k, Show k) => String -> Map k a -> k -> a
Documentation
type CallGraph = Map FunctionName CalleeMap Source #
The CallGraph is a map from a caller function to its CalleeMap.
A new, richer representation of a call site.
Constructors
| CallSite | |
Fields
| |
Describes how a function is called.
Constructors
| DirectCall | |
| IndirectCall |
type FunctionName = Text Source #
A function name is just Text.
type CalleeMap = Map FunctionName (Set CallSite) Source #
A map from a callee's name to the set of ways it's called.
type PointsToMap = Map AbstractLocation (Set AbstractLocation) Source #
The PointsToMap is the data flow fact. It maps a pointer's abstract location to the set of abstract locations it can point to.
type PointsToSummary = Map Context PointsToSummaryData Source #
The full, context-sensitive points-to summary for a function.
data PointsToSummaryData Source #
The summary for a function's points-to analysis in a specific context.
Constructors
| PointsToSummaryData | |
Instances
| Eq PointsToSummaryData Source # | |
Defined in Tokstyle.Analysis.Types Methods (==) :: PointsToSummaryData -> PointsToSummaryData -> Bool # (/=) :: PointsToSummaryData -> PointsToSummaryData -> Bool # | |
| Ord PointsToSummaryData Source # | |
Defined in Tokstyle.Analysis.Types Methods compare :: PointsToSummaryData -> PointsToSummaryData -> Ordering # (<) :: PointsToSummaryData -> PointsToSummaryData -> Bool # (<=) :: PointsToSummaryData -> PointsToSummaryData -> Bool # (>) :: PointsToSummaryData -> PointsToSummaryData -> Bool # (>=) :: PointsToSummaryData -> PointsToSummaryData -> Bool # max :: PointsToSummaryData -> PointsToSummaryData -> PointsToSummaryData # min :: PointsToSummaryData -> PointsToSummaryData -> PointsToSummaryData # | |
| Show PointsToSummaryData Source # | |
Defined in Tokstyle.Analysis.Types Methods showsPrec :: Int -> PointsToSummaryData -> ShowS # show :: PointsToSummaryData -> String # showList :: [PointsToSummaryData] -> ShowS # | |
getCallers :: CallGraph -> FunctionName -> Map FunctionName (Set CallSite) Source #
Helper function to get all functions that call a given function.
data AbstractLocation Source #
Represents a location where a value can be stored. This allows the analysis to distinguish between different variables and fields.
Constructors
| VarLocation Text | A local variable or parameter name. |
| GlobalVarLocation Text | A global or static variable. |
| FieldLocation AbstractLocation Text | A struct/union field, e.g., msg.data |
| DerefLocation AbstractLocation | The memory pointed to by a pointer, e.g., *p |
| ReturnLocation Text | The return value of a function. |
| HeapLocation Int | An abstract location on the heap. |
| FunctionLocation Text | The address of a function. |
Instances
| Eq AbstractLocation Source # | |
Defined in Tokstyle.Analysis.Types Methods (==) :: AbstractLocation -> AbstractLocation -> Bool # (/=) :: AbstractLocation -> AbstractLocation -> Bool # | |
| Ord AbstractLocation Source # | |
Defined in Tokstyle.Analysis.Types Methods compare :: AbstractLocation -> AbstractLocation -> Ordering # (<) :: AbstractLocation -> AbstractLocation -> Bool # (<=) :: AbstractLocation -> AbstractLocation -> Bool # (>) :: AbstractLocation -> AbstractLocation -> Bool # (>=) :: AbstractLocation -> AbstractLocation -> Bool # max :: AbstractLocation -> AbstractLocation -> AbstractLocation # min :: AbstractLocation -> AbstractLocation -> AbstractLocation # | |
| Show AbstractLocation Source # | |
Defined in Tokstyle.Analysis.Types Methods showsPrec :: Int -> AbstractLocation -> ShowS # show :: AbstractLocation -> String # showList :: [AbstractLocation] -> ShowS # | |
toAbstractLocation :: HasCallStack => Node (Lexeme Text) -> AbstractLocation Source #
Helper to convert an LHS expression AST node to an AbstractLocation.