1
1
mirror of https://github.com/github/semantic.git synced 2025-01-05 05:58:34 +03:00

Merge remote-tracking branch 'origin/scopes-and-frames' into heap-frames

This commit is contained in:
joshvera 2018-09-18 12:28:43 -04:00
commit b29573bd2b
6 changed files with 13 additions and 12 deletions

View File

@ -1,6 +1,6 @@
name: semantic
version: 0.4.0
synopsis: Initial project template from stack
synopsis: Framework and service for analyzing and diffing untrusted code.
description: Please see README.md
homepage: http://github.com/github/semantic#readme
author: Rob Rix, Josh Vera

View File

@ -73,7 +73,7 @@ instance Effect (ScopeEnv address) where
runScopeEnv :: (Ord address, Effects effects, Member Fresh effects, Member (Allocator address) effects)
=> Evaluator address value (ScopeEnv address ': effects) a
-> Evaluator address value effects (ScopeGraph address, a)
runScopeEnv evaluator = runState ScopeGraph.emptyGraph (reinterpret handleScopeEnv evaluator)
runScopeEnv evaluator = runState lowerBound (reinterpret handleScopeEnv evaluator)
handleScopeEnv :: forall address value effects a. (Ord address, Member Fresh effects, Member (Allocator address) effects, Effects effects)
=> ScopeEnv address (Eff (ScopeEnv address ': effects)) a

View File

@ -9,7 +9,6 @@ module Data.Abstract.ScopeGraph
, scopeOfRef
, pathOfRef
, declare
, emptyGraph
, reference
, newScope
, associatedScope
@ -31,8 +30,8 @@ data Scope scopeAddress = Scope {
data ScopeGraph scope = ScopeGraph { graph :: Map scope (Scope scope), currentScope :: Maybe scope }
emptyGraph :: Ord scope => ScopeGraph scope
emptyGraph = ScopeGraph mempty Nothing
instance Ord scope => Lower (ScopeGraph scope) where
lowerBound = ScopeGraph mempty Nothing
deriving instance Eq address => Eq (ScopeGraph address)
deriving instance Show address => Show (ScopeGraph address)
@ -99,7 +98,7 @@ reference ref declaration g@ScopeGraph{..} = fromMaybe g $ do
scopes <- Map.lookup edge linkMap
-- Return the first path to the declaration through the scopes.
getFirst (foldMap (First . ap (go currentAddress currentScope) ((path .) . EPath edge)) scopes)
in traverseEdges I <|> traverseEdges P
in traverseEdges Import <|> traverseEdges Lexical
-- | Insert associate the given address to a declaration in the scope graph.
insertDeclarationScope :: Ord address => Declaration -> address -> ScopeGraph address -> ScopeGraph address
@ -158,5 +157,7 @@ newtype Reference = Reference Name
newtype Declaration = Declaration Name
deriving (Eq, Ord, Show)
data EdgeLabel = P | I
-- | The type of edge from a scope to its parent scopes.
-- Either a lexical edge or an import edge in the case of non-lexical edges.
data EdgeLabel = Lexical | Import
deriving (Eq, Ord, Show)

View File

@ -215,8 +215,8 @@ instance Evaluatable Class where
scope <- associatedScope (Declaration name)
(scope,) <$> subtermAddress superclass
let imports = (I,) <$> (fmap pure . catMaybes $ fst <$> supers)
current = maybe mempty (fmap (P, ) . pure . pure) currentScope'
let imports = (Import,) <$> (fmap pure . catMaybes $ fst <$> supers)
current = maybe mempty (fmap (Lexical, ) . pure . pure) currentScope'
edges = Map.fromList (imports <> current)
childScope <- newScope edges
declare (Declaration name) span (Just childScope)

View File

@ -31,7 +31,7 @@ instance ToJSON1 Statements
instance Evaluatable Statements where
eval (Statements xs) = do
currentScope' <- currentScope
let edges = maybe mempty (Map.singleton P . pure) currentScope'
let edges = maybe mempty (Map.singleton Lexical . pure) currentScope'
scope <- newScope edges
withScope scope $ maybe (rvalBox unit) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs)
@ -148,7 +148,7 @@ instance Evaluatable Assignment where
assocScope <- associatedScope (Declaration rhsName)
case assocScope of
Just assocScope' -> do
objectScope <- newScope (Map.singleton I [ assocScope' ])
objectScope <- newScope (Map.singleton Import [ assocScope' ])
putDeclarationScope (Declaration name) objectScope
Nothing -> pure ()
Nothing ->

View File

@ -10,7 +10,7 @@ import Proto3.Suite
import qualified Data.Abstract.Environment as Env
import Data.Abstract.Evaluatable
import Control.Abstract.ScopeGraph
import Control.Abstract.ScopeGraph hiding (Import)
import Data.JSON.Fields
import Diffing.Algorithm
import Language.TypeScript.Resolution