1
1
mirror of https://github.com/github/semantic.git synced 2024-12-20 21:31:48 +03:00

Merge pull request #2180 from github/heap-widening

Flow-insensitive heap widening
This commit is contained in:
Rob Rix 2018-09-18 15:09:47 -04:00 committed by GitHub
commit 0caf4c0dde
10 changed files with 241 additions and 92 deletions

View File

@ -19,7 +19,8 @@ library
hs-source-dirs: src hs-source-dirs: src
exposed-modules: exposed-modules:
-- Analyses & term annotations -- Analyses & term annotations
Analysis.Abstract.Caching Analysis.Abstract.Caching.FlowInsensitive
, Analysis.Abstract.Caching.FlowSensitive
, Analysis.Abstract.Collecting , Analysis.Abstract.Collecting
, Analysis.Abstract.Dead , Analysis.Abstract.Dead
, Analysis.Abstract.Graph , Analysis.Abstract.Graph
@ -35,7 +36,6 @@ library
, Assigning.Assignment.Table , Assigning.Assignment.Table
-- Control structures & interfaces for abstract interpretation -- Control structures & interfaces for abstract interpretation
, Control.Abstract , Control.Abstract
, Control.Abstract.Configuration
, Control.Abstract.Context , Control.Abstract.Context
, Control.Abstract.Environment , Control.Abstract.Environment
, Control.Abstract.Evaluator , Control.Abstract.Evaluator
@ -55,8 +55,6 @@ library
, Data.Abstract.Address.Monovariant , Data.Abstract.Address.Monovariant
, Data.Abstract.Address.Precise , Data.Abstract.Address.Precise
, Data.Abstract.BaseError , Data.Abstract.BaseError
, Data.Abstract.Cache
, Data.Abstract.Configuration
, Data.Abstract.Declarations , Data.Abstract.Declarations
, Data.Abstract.Environment , Data.Abstract.Environment
, Data.Abstract.Evaluatable , Data.Abstract.Evaluatable

View File

@ -0,0 +1,173 @@
{-# LANGUAGE GADTs, GeneralizedNewtypeDeriving, TypeOperators #-}
module Analysis.Abstract.Caching.FlowInsensitive
( cachingTerms
, convergingModules
, caching
) where
import Control.Abstract
import Data.Abstract.BaseError
import Data.Abstract.Environment
import Data.Abstract.Module
import Data.Abstract.Ref
import Data.Map.Monoidal as Monoidal
import Prologue
-- | Look up the set of values for a given configuration in the in-cache.
consultOracle :: (Member (Reader (Cache term address)) effects, Ord address, Ord term)
=> Configuration term address
-> TermEvaluator term address value effects (Set (ValueRef address))
consultOracle configuration = fromMaybe mempty . cacheLookup configuration <$> ask
-- | Run an action with the given in-cache.
withOracle :: Member (Reader (Cache term address)) effects
=> Cache term address
-> TermEvaluator term address value effects a
-> TermEvaluator term address value effects a
withOracle cache = local (const cache)
-- | Look up the set of values for a given configuration in the out-cache.
lookupCache :: (Member (State (Cache term address)) effects, Ord address, Ord term)
=> Configuration term address
-> TermEvaluator term address value effects (Maybe (Set (ValueRef address)))
lookupCache configuration = cacheLookup configuration <$> get
-- | Run an action, caching its result and 'Heap' under the given configuration.
cachingConfiguration :: (Member (State (Cache term address)) effects, Ord address, Ord term)
=> Configuration term address
-> Set (ValueRef address)
-> TermEvaluator term address value effects (ValueRef address)
-> TermEvaluator term address value effects (ValueRef address)
cachingConfiguration configuration values action = do
modify' (cacheSet configuration values)
result <- action
result <$ modify' (cacheInsert configuration result)
putCache :: Member (State (Cache term address)) effects
=> Cache term address
-> TermEvaluator term address value effects ()
putCache = put
-- | Run an action starting from an empty out-cache, and return the out-cache afterwards.
isolateCache :: (Member (State (Cache term address)) effects, Member (State (Heap address value)) effects)
=> TermEvaluator term address value effects a
-> TermEvaluator term address value effects (Cache term address, Heap address value)
isolateCache action = putCache lowerBound *> action *> ((,) <$> get <*> get)
-- | Analyze a term using the in-cache as an oracle & storing the results of the analysis in the out-cache.
cachingTerms :: ( Corecursive term
, Member (Env address) effects
, Member NonDet effects
, Member (Reader (Cache term address)) effects
, Member (Reader (Live address)) effects
, Member (State (Cache term address)) effects
, Ord address
, Ord term
)
=> SubtermAlgebra (Base term) term (TermEvaluator term address value effects (ValueRef address))
-> SubtermAlgebra (Base term) term (TermEvaluator term address value effects (ValueRef address))
cachingTerms recur term = do
c <- getConfiguration (embedSubterm term)
cached <- lookupCache c
case cached of
Just values -> scatter values
Nothing -> do
values <- consultOracle c
cachingConfiguration c values (recur term)
convergingModules :: ( AbstractValue address value effects
, Effects effects
, Eq value
, Member (Env address) effects
, Member Fresh effects
, Member NonDet effects
, Member (Reader (Cache term address)) effects
, Member (Reader (Live address)) effects
, Member (Reader ModuleInfo) effects
, Member (Reader Span) effects
, Member (Resumable (BaseError (EnvironmentError address))) effects
, Member (State (Cache term address)) effects
, Member (State (Heap address value)) effects
, Ord address
, Ord term
)
=> SubtermAlgebra Module term (TermEvaluator term address value effects address)
-> SubtermAlgebra Module term (TermEvaluator term address value effects address)
convergingModules recur m = do
c <- getConfiguration (subterm (moduleBody m))
heap <- TermEvaluator getHeap
-- Convergence here is predicated upon an Eq instance, not α-equivalence
(cache, _) <- converge (lowerBound, heap) (\ (prevCache, _) -> isolateCache $ do
TermEvaluator (putEvalContext (configurationContext c))
-- We need to reset fresh generation so that this invocation converges.
resetFresh 0 $
-- This is subtle: though the calling context supports nondeterminism, we want
-- to corral all the nondeterminism that happens in this @eval@ invocation, so
-- that it doesn't "leak" to the calling context and diverge (otherwise this
-- would never complete). We dont need to use the values, so we 'gather' the
-- nondeterministic values into @()@.
withOracle prevCache (gatherM (const ()) (recur m)))
TermEvaluator (address =<< runTermEvaluator (maybe empty scatter (cacheLookup c cache)))
-- | Iterate a monadic action starting from some initial seed until the results converge.
--
-- This applies the Kleene fixed-point theorem to finitize a monotone action. cf https://en.wikipedia.org/wiki/Kleene_fixed-point_theorem
converge :: (Eq a, Monad m)
=> a -- ^ An initial seed value to iterate from.
-> (a -> m a) -- ^ A monadic action to perform at each iteration, starting from the result of the previous iteration or from the seed value for the first iteration.
-> m a -- ^ A computation producing the least fixed point (the first value at which the actions converge).
converge seed f = loop seed
where loop x = do
x' <- f x
if x' == x then
pure x
else
loop x'
-- | Nondeterministically write each of a collection of stores & return their associated results.
scatter :: (Foldable t, Member NonDet effects) => t (ValueRef address) -> TermEvaluator term address value effects (ValueRef address)
scatter = foldMapA pure
-- | Get the current 'Configuration' with a passed-in term.
getConfiguration :: (Member (Reader (Live address)) effects, Member (Env address) effects)
=> term
-> TermEvaluator term address value effects (Configuration term address)
getConfiguration term = Configuration term <$> TermEvaluator askRoots <*> TermEvaluator getEvalContext
caching :: Effects effects => TermEvaluator term address value (NonDet ': Reader (Cache term address) ': State (Cache term address) ': effects) a -> TermEvaluator term address value effects (Cache term address, [a])
caching
= runState lowerBound
. runReader lowerBound
. runNonDet
-- | A map of 'Configuration's to 'Set's of resulting values & 'Heap's.
newtype Cache term address = Cache { unCache :: Monoidal.Map (Configuration term address) (Set (ValueRef address)) }
deriving (Eq, Lower, Monoid, Ord, Reducer (Configuration term address, ValueRef address), Semigroup)
-- | A single point in a programs execution.
data Configuration term address = Configuration
{ configurationTerm :: term -- ^ The “instruction,” i.e. the current term to evaluate.
, configurationRoots :: Live address -- ^ The set of rooted addresses.
, configurationContext :: EvalContext address -- ^ The evaluation context in 'configurationTerm'.
}
deriving (Eq, Ord, Show)
-- | Look up the resulting value & 'Heap' for a given 'Configuration'.
cacheLookup :: (Ord address, Ord term) => Configuration term address -> Cache term address -> Maybe (Set (ValueRef address))
cacheLookup key = Monoidal.lookup key . unCache
-- | Set the resulting value & 'Heap' for a given 'Configuration', overwriting any previous entry.
cacheSet :: (Ord address, Ord term) => Configuration term address -> Set (ValueRef address) -> Cache term address -> Cache term address
cacheSet key value = Cache . Monoidal.insert key value . unCache
-- | Insert the resulting value & 'Heap' for a given 'Configuration', appending onto any previous entry.
cacheInsert :: (Ord address, Ord term) => Configuration term address -> ValueRef address -> Cache term address -> Cache term address
cacheInsert = curry cons
instance (Show term, Show address) => Show (Cache term address) where
showsPrec d = showsUnaryWith showsPrec "Cache" d . map (second toList) . Monoidal.pairs . unCache

View File

@ -1,17 +1,16 @@
{-# LANGUAGE GADTs, TypeOperators #-} {-# LANGUAGE ConstraintKinds, GADTs, GeneralizedNewtypeDeriving, TypeOperators #-}
module Analysis.Abstract.Caching module Analysis.Abstract.Caching.FlowSensitive
( cachingTerms ( cachingTerms
, convergingModules , convergingModules
, caching , caching
) where ) where
import Control.Abstract.Configuration
import Control.Abstract import Control.Abstract
import Data.Abstract.Cache
import Data.Abstract.BaseError import Data.Abstract.BaseError
import Data.Abstract.Environment import Data.Abstract.Environment
import Data.Abstract.Module import Data.Abstract.Module
import Data.Abstract.Ref import Data.Abstract.Ref
import Data.Map.Monoidal as Monoidal
import Prologue import Prologue
-- | Look up the set of values for a given configuration in the in-cache. -- | Look up the set of values for a given configuration in the in-cache.
@ -129,9 +128,53 @@ converge seed f = loop seed
scatter :: (Foldable t, Member NonDet effects, Member (State (Heap address value)) effects) => t (Cached address value) -> TermEvaluator term address value effects (ValueRef address) scatter :: (Foldable t, Member NonDet effects, Member (State (Heap address value)) effects) => t (Cached address value) -> TermEvaluator term address value effects (ValueRef address)
scatter = foldMapA (\ (Cached value heap') -> TermEvaluator (putHeap heap') $> value) scatter = foldMapA (\ (Cached value heap') -> TermEvaluator (putHeap heap') $> value)
-- | Get the current 'Configuration' with a passed-in term.
getConfiguration :: (Member (Reader (Live address)) effects, Member (Env address) effects, Member (State (Heap address value)) effects)
=> term
-> TermEvaluator term address value effects (Configuration term address value)
getConfiguration term = Configuration term <$> TermEvaluator askRoots <*> TermEvaluator getEvalContext <*> TermEvaluator getHeap
caching :: Effects effects => TermEvaluator term address value (NonDet ': Reader (Cache term address value) ': State (Cache term address value) ': effects) a -> TermEvaluator term address value effects (Cache term address value, [a]) caching :: Effects effects => TermEvaluator term address value (NonDet ': Reader (Cache term address value) ': State (Cache term address value) ': effects) a -> TermEvaluator term address value effects (Cache term address value, [a])
caching caching
= runState lowerBound = runState lowerBound
. runReader lowerBound . runReader lowerBound
. runNonDet . runNonDet
-- | A map of 'Configuration's to 'Set's of resulting values & 'Heap's.
newtype Cache term address value = Cache { unCache :: Monoidal.Map (Configuration term address value) (Set (Cached address value)) }
deriving (Eq, Lower, Monoid, Ord, Reducer (Configuration term address value, Cached address value), Semigroup)
-- | A single point in a programs execution.
data Configuration term address value = Configuration
{ configurationTerm :: term -- ^ The “instruction,” i.e. the current term to evaluate.
, configurationRoots :: Live address -- ^ The set of rooted addresses.
, configurationContext :: EvalContext address -- ^ The evaluation context in 'configurationTerm'.
, configurationHeap :: Heap address value -- ^ The heap of values.
}
deriving (Eq, Ord, Show)
data Cached address value = Cached
{ cachedValue :: ValueRef address
, cachedHeap :: Heap address value
}
deriving (Eq, Ord, Show)
type Cacheable term address value = (Ord address, Ord term, Ord value)
-- | Look up the resulting value & 'Heap' for a given 'Configuration'.
cacheLookup :: Cacheable term address value => Configuration term address value -> Cache term address value -> Maybe (Set (Cached address value))
cacheLookup key = Monoidal.lookup key . unCache
-- | Set the resulting value & 'Heap' for a given 'Configuration', overwriting any previous entry.
cacheSet :: Cacheable term address value => Configuration term address value -> Set (Cached address value) -> Cache term address value -> Cache term address value
cacheSet key value = Cache . Monoidal.insert key value . unCache
-- | Insert the resulting value & 'Heap' for a given 'Configuration', appending onto any previous entry.
cacheInsert :: Cacheable term address value => Configuration term address value -> Cached address value -> Cache term address value -> Cache term address value
cacheInsert = curry cons
instance (Show term, Show address, Show value) => Show (Cache term address value) where
showsPrec d = showsUnaryWith showsPrec "Cache" d . map (second toList) . Monoidal.pairs . unCache

View File

@ -4,9 +4,9 @@ module Analysis.Abstract.Tracing
, tracing , tracing
) where ) where
import Control.Abstract.Configuration
import Control.Abstract hiding (trace) import Control.Abstract hiding (trace)
import Control.Monad.Effect.Writer import Control.Monad.Effect.Writer
import Data.Abstract.Environment
import Data.Semigroup.Reducer as Reducer import Data.Semigroup.Reducer as Reducer
import Prologue import Prologue
@ -14,7 +14,6 @@ import Prologue
-- --
-- Instantiating @trace@ to @[]@ yields a linear trace analysis, while @Set@ yields a reachable state analysis. -- Instantiating @trace@ to @[]@ yields a linear trace analysis, while @Set@ yields a reachable state analysis.
tracingTerms :: ( Corecursive term tracingTerms :: ( Corecursive term
, Member (Reader (Live address)) effects
, Member (Env address) effects , Member (Env address) effects
, Member (State (Heap address value)) effects , Member (State (Heap address value)) effects
, Member (Writer (trace (Configuration term address value))) effects , Member (Writer (trace (Configuration term address value))) effects
@ -30,3 +29,18 @@ trace = tell
tracing :: (Monoid (trace (Configuration term address value)), Effects effects) => TermEvaluator term address value (Writer (trace (Configuration term address value)) ': effects) a -> TermEvaluator term address value effects (trace (Configuration term address value), a) tracing :: (Monoid (trace (Configuration term address value)), Effects effects) => TermEvaluator term address value (Writer (trace (Configuration term address value)) ': effects) a -> TermEvaluator term address value effects (trace (Configuration term address value), a)
tracing = runWriter tracing = runWriter
-- | Get the current 'Configuration' with a passed-in term.
getConfiguration :: (Member (Env address) effects, Member (State (Heap address value)) effects)
=> term
-> TermEvaluator term address value effects (Configuration term address value)
getConfiguration term = Configuration term <$> TermEvaluator getEvalContext <*> TermEvaluator getHeap
-- | A single point in a programs execution.
data Configuration term address value = Configuration
{ configurationTerm :: term -- ^ The “instruction,” i.e. the current term to evaluate.
, configurationContext :: EvalContext address -- ^ The evaluation context in 'configurationTerm'.
, configurationHeap :: Heap address value -- ^ The heap of values.
}
deriving (Eq, Ord, Show)

View File

@ -1,15 +0,0 @@
module Control.Abstract.Configuration
( getConfiguration
) where
import Control.Abstract.Environment
import Control.Abstract.Heap
import Control.Abstract.Roots
import Control.Abstract.TermEvaluator
-- | Get the current 'Configuration' with a passed-in term.
getConfiguration :: (Member (Reader (Live address)) effects, Member (Env address) effects, Member (State (Heap address value)) effects)
=> term
-> TermEvaluator term address value effects (Configuration term address value)
getConfiguration term = Configuration term <$> TermEvaluator askRoots <*> TermEvaluator getEvalContext <*> TermEvaluator getHeap

View File

@ -1,7 +1,6 @@
{-# LANGUAGE GADTs, KindSignatures, RankNTypes, TypeOperators, UndecidableInstances #-} {-# LANGUAGE GADTs, KindSignatures, RankNTypes, TypeOperators, UndecidableInstances #-}
module Control.Abstract.Heap module Control.Abstract.Heap
( Heap ( Heap
, Configuration(..)
, Live , Live
, getHeap , getHeap
, putHeap , putHeap
@ -22,7 +21,6 @@ module Control.Abstract.Heap
import Control.Abstract.Evaluator import Control.Abstract.Evaluator
import Control.Abstract.Roots import Control.Abstract.Roots
import Data.Abstract.Configuration
import Data.Abstract.BaseError import Data.Abstract.BaseError
import Data.Abstract.Heap import Data.Abstract.Heap
import Data.Abstract.Live import Data.Abstract.Live

View File

@ -1,48 +0,0 @@
{-# LANGUAGE ConstraintKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
module Data.Abstract.Cache
( Cache
, Cached (..)
, Cacheable
, cacheLookup
, cacheSet
, cacheInsert
, cacheKeys
) where
import Data.Abstract.Configuration
import Data.Abstract.Heap
import Data.Abstract.Ref
import Data.Map.Monoidal as Monoidal
import Prologue
-- | A map of 'Configuration's to 'Set's of resulting values & 'Heap's.
newtype Cache term address value = Cache { unCache :: Monoidal.Map (Configuration term address value) (Set (Cached address value)) }
deriving (Eq, Lower, Monoid, Ord, Reducer (Configuration term address value, Cached address value), Semigroup)
data Cached address value = Cached
{ cachedValue :: ValueRef address
, cachedHeap :: Heap address value
}
deriving (Eq, Ord, Show)
type Cacheable term address value = (Ord address, Ord term, Ord value)
-- | Look up the resulting value & 'Heap' for a given 'Configuration'.
cacheLookup :: Cacheable term address value => Configuration term address value -> Cache term address value -> Maybe (Set (Cached address value))
cacheLookup key = Monoidal.lookup key . unCache
-- | Set the resulting value & 'Heap' for a given 'Configuration', overwriting any previous entry.
cacheSet :: Cacheable term address value => Configuration term address value -> Set (Cached address value) -> Cache term address value -> Cache term address value
cacheSet key value = Cache . Monoidal.insert key value . unCache
-- | Insert the resulting value & 'Heap' for a given 'Configuration', appending onto any previous entry.
cacheInsert :: Cacheable term address value => Configuration term address value -> Cached address value -> Cache term address value -> Cache term address value
cacheInsert = curry cons
-- | Return all 'Configuration's in the provided cache.
cacheKeys :: Cache term address value -> [Configuration term address value]
cacheKeys = Monoidal.keys . unCache
instance (Show term, Show address, Show value) => Show (Cache term address value) where
showsPrec d = showsUnaryWith showsPrec "Cache" d . map (second toList) . Monoidal.pairs . unCache

View File

@ -1,14 +0,0 @@
module Data.Abstract.Configuration ( Configuration (..) ) where
import Data.Abstract.Environment
import Data.Abstract.Heap
import Data.Abstract.Live
-- | A single point in a programs execution.
data Configuration term address value = Configuration
{ configurationTerm :: term -- ^ The “instruction,” i.e. the current term to evaluate.
, configurationRoots :: Live address -- ^ The set of rooted addresses.
, configurationContext :: EvalContext address -- ^ The evaluation context in 'configurationTerm'.
, configurationHeap :: Heap address value -- ^ The heap of values.
}
deriving (Eq, Ord, Show)

View File

@ -26,7 +26,7 @@ module Semantic.Graph
import Prelude hiding (readFile) import Prelude hiding (readFile)
import Analysis.Abstract.Caching import Analysis.Abstract.Caching.FlowInsensitive
import Analysis.Abstract.Collecting import Analysis.Abstract.Collecting
import Analysis.Abstract.Graph as Graph import Analysis.Abstract.Graph as Graph
import Control.Abstract import Control.Abstract
@ -111,8 +111,8 @@ runCallGraph lang includePackages modules package = do
runGraphAnalysis runGraphAnalysis
= runTermEvaluator @_ @(Hole (Maybe Name) (Located Monovariant)) @Abstract = runTermEvaluator @_ @(Hole (Maybe Name) (Located Monovariant)) @Abstract
. graphing @_ @_ @(Maybe Name) @Monovariant . graphing @_ @_ @(Maybe Name) @Monovariant
. caching
. runState (lowerBound @(Heap (Hole (Maybe Name) (Located Monovariant)) Abstract)) . runState (lowerBound @(Heap (Hole (Maybe Name) (Located Monovariant)) Abstract))
. caching
. runFresh 0 . runFresh 0
. resumingLoadError . resumingLoadError
. resumingUnspecialized . resumingUnspecialized

View File

@ -4,7 +4,7 @@ module Semantic.Util where
import Prelude hiding (id, (.), readFile) import Prelude hiding (id, (.), readFile)
import Analysis.Abstract.Caching import Analysis.Abstract.Caching.FlowSensitive
import Analysis.Abstract.Collecting import Analysis.Abstract.Collecting
import Control.Abstract import Control.Abstract
import Control.Category import Control.Category