mirror of
https://github.com/github/semantic.git
synced 2024-12-20 13:21:59 +03:00
Merge branch 'new-expressions' of https://github.com/github/semantic into new-expressions
This commit is contained in:
commit
512f4246cb
@ -55,7 +55,7 @@ import qualified Data.Abstract.Heap as Heap
|
||||
import Data.Abstract.Live
|
||||
import Data.Abstract.Module (ModuleInfo)
|
||||
import Data.Abstract.Name
|
||||
import Data.Abstract.ScopeGraph (Path (..), putDeclarationScopeAtPosition)
|
||||
import Data.Abstract.ScopeGraph (Path (..), Relation(..), putDeclarationScopeAtPosition)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Span (Span, emptySpan)
|
||||
import Prologue
|
||||
@ -174,11 +174,12 @@ define :: ( HasCallStack
|
||||
, Carrier sig m
|
||||
)
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> Evaluator term address value m value
|
||||
-> Evaluator term address value m ()
|
||||
define declaration def = withCurrentCallStack callStack $ do
|
||||
define declaration rel def = withCurrentCallStack callStack $ do
|
||||
-- TODO: This span is still wrong.
|
||||
declare declaration emptySpan Nothing
|
||||
declare declaration rel emptySpan Nothing
|
||||
slot <- lookupDeclaration declaration
|
||||
value <- def
|
||||
assign slot value
|
||||
|
@ -33,18 +33,19 @@ defineBuiltIn :: ( HasCallStack
|
||||
, Carrier sig m
|
||||
)
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> BuiltIn
|
||||
-> Evaluator term address value m ()
|
||||
defineBuiltIn declaration value = withCurrentCallStack callStack $ do
|
||||
defineBuiltIn declaration rel value = withCurrentCallStack callStack $ do
|
||||
currentScope' <- currentScope
|
||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||
associatedScope <- newScope lexicalEdges
|
||||
-- TODO: This span is still wrong.
|
||||
declare declaration emptySpan (Just associatedScope)
|
||||
declare declaration rel emptySpan (Just associatedScope)
|
||||
|
||||
param <- gensym
|
||||
withScope associatedScope $ do
|
||||
declare (Declaration param) emptySpan Nothing
|
||||
declare (Declaration param) rel emptySpan Nothing
|
||||
|
||||
slot <- lookupDeclaration declaration
|
||||
value <- builtIn associatedScope value
|
||||
@ -70,7 +71,7 @@ defineClass :: ( AbstractValue term address value m
|
||||
-> [Declaration]
|
||||
-> Evaluator term address value m a
|
||||
-> Evaluator term address value m ()
|
||||
defineClass declaration superclasses body = void . define declaration $ do
|
||||
defineClass declaration superclasses body = void . define declaration Default $ do
|
||||
currentScope' <- currentScope
|
||||
|
||||
superScopes <- for superclasses associatedScope
|
||||
@ -105,7 +106,7 @@ defineNamespace :: ( AbstractValue term address value m
|
||||
=> Declaration
|
||||
-> Evaluator term address value m a
|
||||
-> Evaluator term address value m ()
|
||||
defineNamespace declaration@Declaration{..} body = void . define declaration $ do
|
||||
defineNamespace declaration@Declaration{..} body = void . define declaration Default $ do
|
||||
withChildFrame declaration $ \frame -> do
|
||||
_ <- body
|
||||
namespace unDeclaration frame
|
||||
|
@ -9,6 +9,7 @@ module Control.Abstract.ScopeGraph
|
||||
, ScopeGraph
|
||||
, ScopeError(..)
|
||||
, Reference(..)
|
||||
, Relation(..)
|
||||
, EdgeLabel(..)
|
||||
, CurrentScope(..)
|
||||
, currentScope
|
||||
@ -41,7 +42,7 @@ import Control.Effect.Carrier
|
||||
import Data.Abstract.BaseError
|
||||
import Data.Abstract.Module
|
||||
import Data.Abstract.Name hiding (name)
|
||||
import Data.Abstract.ScopeGraph (Declaration (..), EdgeLabel, Reference, Scope (..), ScopeGraph, Slot (..))
|
||||
import Data.Abstract.ScopeGraph (Declaration(..), EdgeLabel, Reference, Relation(..), Scope (..), ScopeGraph, Slot(..))
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Span
|
||||
import Prelude hiding (lookup)
|
||||
@ -56,12 +57,13 @@ declare :: ( Carrier sig m
|
||||
, Ord address
|
||||
)
|
||||
=> Declaration
|
||||
-> Relation
|
||||
-> Span
|
||||
-> Maybe address
|
||||
-> Evaluator term address value m ()
|
||||
declare decl span scope = do
|
||||
declare decl rel span scope = do
|
||||
currentAddress <- currentScope
|
||||
modify (fst . ScopeGraph.declare decl span scope currentAddress)
|
||||
modify (fst . ScopeGraph.declare decl rel span scope currentAddress)
|
||||
|
||||
putDeclarationScope :: (Ord address, Member (Reader (CurrentScope address)) sig, Member (State (ScopeGraph address)) sig, Carrier sig m) => Declaration -> address -> Evaluator term address value m ()
|
||||
putDeclarationScope decl assocScope = do
|
||||
|
@ -26,6 +26,7 @@ import Data.Abstract.Declarations as X
|
||||
import Data.Abstract.FreeVariables as X
|
||||
import Data.Abstract.Module
|
||||
import Data.Abstract.Name as X
|
||||
import Data.Abstract.ScopeGraph (Relation(..))
|
||||
import Data.Language
|
||||
import Data.Scientific (Scientific)
|
||||
import Data.Semigroup.App
|
||||
@ -135,26 +136,26 @@ instance HasPrelude 'PHP
|
||||
|
||||
instance HasPrelude 'Python where
|
||||
definePrelude _ =
|
||||
defineBuiltIn (Declaration $ X.name "print") Print
|
||||
defineBuiltIn (Declaration $ X.name "print") Default Print
|
||||
|
||||
instance HasPrelude 'Ruby where
|
||||
definePrelude _ = do
|
||||
defineSelf
|
||||
|
||||
defineBuiltIn (Declaration $ X.name "puts") Print
|
||||
defineBuiltIn (Declaration $ X.name "puts") Default Print
|
||||
|
||||
defineClass (Declaration (X.name "Object")) [] $ do
|
||||
defineBuiltIn (Declaration $ X.name "inspect") Show
|
||||
defineBuiltIn (Declaration $ X.name "inspect") Default Show
|
||||
|
||||
instance HasPrelude 'TypeScript where
|
||||
definePrelude _ = do
|
||||
defineSelf
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Print
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Default Print
|
||||
|
||||
instance HasPrelude 'JavaScript where
|
||||
definePrelude _ = do
|
||||
defineSelf
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Print
|
||||
defineNamespace (Declaration (X.name "console")) $ defineBuiltIn (Declaration $ X.name "log") Default Print
|
||||
|
||||
defineSelf :: ( AbstractValue term address value m
|
||||
, Carrier sig m
|
||||
@ -172,7 +173,8 @@ defineSelf :: ( AbstractValue term address value m
|
||||
=> Evaluator term address value m ()
|
||||
defineSelf = do
|
||||
let self = Declaration $ X.name "__self"
|
||||
declare self emptySpan Nothing
|
||||
-- TODO: Should `self` be given a special Relation?
|
||||
declare self Default emptySpan Nothing
|
||||
slot <- lookupDeclaration self
|
||||
assign slot =<< object =<< currentFrame
|
||||
|
||||
|
@ -18,6 +18,7 @@ module Data.Abstract.ScopeGraph
|
||||
, Position(..)
|
||||
, reference
|
||||
, Reference(..) -- TODO don't export these constructors
|
||||
, Relation(..)
|
||||
, ScopeGraph(..)
|
||||
, lookupScope
|
||||
, lookupScopePath
|
||||
@ -44,11 +45,11 @@ data Slot address = Slot { frameAddress :: address, position :: Position }
|
||||
data Relation = Default | InstanceOf
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
data Data address = Data {
|
||||
declaration :: Declaration
|
||||
, relation :: Relation
|
||||
, span :: Span
|
||||
, scopeAddress :: Maybe address
|
||||
data Data scopeAddress = Data {
|
||||
dataDeclaration :: Declaration
|
||||
, dataRelation :: Relation
|
||||
, dataSpan :: Span
|
||||
, dataAssociatedScope :: Maybe scopeAddress
|
||||
}
|
||||
deriving (Eq, Show, Ord, Generic, NFData)
|
||||
|
||||
@ -125,12 +126,12 @@ lookupScope scope = Map.lookup scope . unScopeGraph
|
||||
|
||||
-- Declare a declaration with a span and an associated scope in the scope graph.
|
||||
-- TODO: Return the whole value in Maybe or Either.
|
||||
declare :: Ord scope => Declaration -> Span -> Relation -> Maybe scope -> scope -> ScopeGraph scope -> (ScopeGraph scope, Maybe Position)
|
||||
declare decl declSpan rel assocScope currentScope g = fromMaybe (g, Nothing) $ do
|
||||
declare :: Ord scope => Declaration -> Relation -> Span -> Maybe scope -> scope -> ScopeGraph scope -> (ScopeGraph scope, Maybe Position)
|
||||
declare decl rel declSpan assocScope currentScope g = fromMaybe (g, Nothing) $ do
|
||||
scope <- lookupScope currentScope g
|
||||
|
||||
dataSeq <- ddataOfScope currentScope g
|
||||
case Seq.findIndexR (\Data{..} -> decl == declaration && declSpan == span && rel == relation) dataSeq of
|
||||
case Seq.findIndexR (\Data{..} -> decl == dataDeclaration && declSpan == dataSpan && rel == dataRelation) dataSeq of
|
||||
Just index -> pure (g, Just (Position index))
|
||||
Nothing -> do
|
||||
let newScope = scope { declarations = declarations scope Seq.|> Data decl rel declSpan assocScope }
|
||||
@ -177,23 +178,23 @@ pathToDeclaration decl address g = DPath decl . snd <$> lookupDeclaration (unDec
|
||||
insertReference :: Reference -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
|
||||
insertReference ref path scope = scope { references = Map.insert ref path (references scope) }
|
||||
|
||||
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe ((Declaration, (Span, Maybe scopeAddress)), Position)
|
||||
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Data scopeAddress, Position)
|
||||
lookupDeclaration name scope g = do
|
||||
dataSeq <- ddataOfScope scope g
|
||||
index <- Seq.findIndexR (\Data{..} -> Declaration name == declaration) dataSeq
|
||||
index <- Seq.findIndexR (\Data{..} -> Declaration name == dataDeclaration) dataSeq
|
||||
(, Position index) <$> Seq.lookup index dataSeq
|
||||
|
||||
declarationNames :: Ord address => [EdgeLabel] -> Scope address -> ScopeGraph address -> Set Declaration
|
||||
declarationNames edgeLabels scope scopeGraph = localDeclarations <> edgeNames
|
||||
where addresses = join (Map.elems $ Map.restrictKeys (edges scope) (Set.fromList edgeLabels))
|
||||
edgeNames = flip foldMap addresses $ \address -> maybe mempty (flip (declarationNames edgeLabels) scopeGraph) (lookupScope address scopeGraph)
|
||||
localDeclarations = Set.fromList . toList . fmap fst $ declarations scope
|
||||
localDeclarations = Set.fromList . toList . fmap dataDeclaration $ declarations scope
|
||||
|
||||
|
||||
putDeclarationScopeAtPosition :: Ord scopeAddress => scopeAddress -> Position -> Maybe scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
putDeclarationScopeAtPosition scope position assocScope g@(ScopeGraph graph) = fromMaybe g $ do
|
||||
dataSeq <- ddataOfScope scope g
|
||||
let seq = Seq.adjust' (\(d, (span, _)) -> (d, (span, assocScope))) (unPosition position) dataSeq
|
||||
let seq = Seq.adjust' (\Data{..} -> Data dataDeclaration dataRelation dataSpan assocScope) (unPosition position) dataSeq
|
||||
pure $ ScopeGraph (Map.adjust (\s -> s { declarations = seq }) scope graph)
|
||||
|
||||
lookupReference :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
|
||||
@ -207,21 +208,22 @@ insertEdge label target currentAddress g@(ScopeGraph graph) = fromMaybe g $ do
|
||||
pure (ScopeGraph (Map.insert currentAddress newScope graph))
|
||||
|
||||
|
||||
-- | Insert associate the given associated scope into the declaration in the scope graph.
|
||||
-- | Update the 'Scope' containing a 'Declaration' with an associated scope address.
|
||||
-- Returns an unmodified 'ScopeGraph' if the 'Declaration' cannot be found with the given scope address.
|
||||
insertDeclarationScope :: Ord scopeAddress => Declaration -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
insertDeclarationScope decl@Declaration{..} address currentAddress g@(ScopeGraph graph) = fromMaybe g $ do
|
||||
declScope <- pathDeclarationScope currentAddress =<< lookupScopePath unDeclaration currentAddress g
|
||||
(span, position) <- (fst . snd . fst &&& unPosition . snd) <$> lookupDeclaration unDeclaration declScope g
|
||||
scope <- lookupScope declScope g
|
||||
pure $ ScopeGraph (Map.insert declScope (scope { declarations = Seq.adjust (const (decl, (span, Just address))) position (declarations scope) }) graph)
|
||||
insertDeclarationScope decl@Declaration{..} associatedScopeAddress scopeAddress g = fromMaybe g $ do
|
||||
declScopeAddress <- pathDeclarationScope scopeAddress =<< lookupScopePath unDeclaration scopeAddress g
|
||||
scope <- lookupScope declScopeAddress g
|
||||
(declData, position) <- (id . fst &&& unPosition . snd) <$> lookupDeclaration unDeclaration declScopeAddress g
|
||||
pure $ insertScope declScopeAddress (scope { declarations = Seq.adjust (const (Data decl (dataRelation declData) (dataSpan declData) (Just associatedScopeAddress))) position (declarations scope) }) g
|
||||
|
||||
-- | Insert a declaration span into the declaration in the scope graph.
|
||||
insertDeclarationSpan :: Ord scopeAddress => Declaration -> Span -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
insertDeclarationSpan decl@Declaration{..} span g@(ScopeGraph graph) = fromMaybe g $ do
|
||||
declScope <- scopeOfDeclaration decl g
|
||||
(associatedScope, position) <- (snd . snd . fst &&& unPosition . snd) <$> lookupDeclaration unDeclaration declScope g
|
||||
scope <- lookupScope declScope g
|
||||
pure $ ScopeGraph (Map.insert declScope (scope { declarations = Seq.adjust (const (decl, (span, associatedScope))) position (declarations scope) }) graph)
|
||||
insertDeclarationSpan decl@Declaration{..} span g = fromMaybe g $ do
|
||||
declScopeAddress <- scopeOfDeclaration decl g
|
||||
(declData, position) <- (id . fst &&& unPosition . snd) <$> lookupDeclaration unDeclaration declScopeAddress g
|
||||
scope <- lookupScope declScopeAddress g
|
||||
pure $ insertScope declScopeAddress (scope { declarations = Seq.adjust (const (Data decl (dataRelation declData) span (dataAssociatedScope declData))) position (declarations scope) }) g
|
||||
|
||||
-- | Insert a new scope with the given address and edges into the scope graph.
|
||||
newScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
|
||||
@ -257,7 +259,7 @@ scopeOfDeclaration Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
|
||||
associatedScope :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
|
||||
associatedScope Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
|
||||
where
|
||||
go = foldr (\ scope -> ((lookupDeclaration unDeclaration scope g >>= snd . snd . fst) <|>)) Nothing
|
||||
go = foldr (\ scope -> ((lookupDeclaration unDeclaration scope g >>= dataAssociatedScope . fst) <|>)) Nothing
|
||||
|
||||
newtype Reference = Reference { unReference :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
@ -36,7 +36,7 @@ instance Evaluatable Function where
|
||||
|
||||
params <- withScope associatedScope . for functionParameters $ \paramNode -> do
|
||||
param <- maybeM (throwEvalError $ NoNameError paramNode) (declaredName paramNode)
|
||||
param <$ declare (Declaration param) span Nothing
|
||||
param <$ declare (Declaration param) Default span Nothing
|
||||
|
||||
addr <- lookupDeclaration (Declaration name)
|
||||
v <- function name params functionBody associatedScope
|
||||
@ -56,7 +56,7 @@ declareFunction name span = do
|
||||
currentScope' <- currentScope
|
||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||
associatedScope <- newScope lexicalEdges
|
||||
declare (Declaration name) span (Just associatedScope)
|
||||
declare (Declaration name) Default span (Just associatedScope)
|
||||
pure associatedScope
|
||||
|
||||
instance Tokenize Function where
|
||||
@ -92,10 +92,12 @@ instance Evaluatable Method where
|
||||
|
||||
params <- withScope associatedScope $ do
|
||||
let self = Name.name "__self"
|
||||
declare (Declaration self) emptySpan Nothing
|
||||
-- TODO: Should we give `self` a special Relation?
|
||||
declare (Declaration self) Default emptySpan Nothing
|
||||
fmap (self :) . for methodParameters $ \paramNode -> do
|
||||
param <- maybeM (throwEvalError $ NoNameError paramNode) (declaredName paramNode)
|
||||
param <$ declare (Declaration param) span Nothing
|
||||
-- TODO: Should we treat params as a special Relation? I've left this as an `InstanceOf` for now.
|
||||
param <$ declare (Declaration param) InstanceOf span Nothing
|
||||
|
||||
addr <- lookupDeclaration (Declaration name)
|
||||
v <- function name params methodBody associatedScope
|
||||
@ -164,7 +166,7 @@ instance Evaluatable VariableDeclaration where
|
||||
eval eval _ (VariableDeclaration decs) = do
|
||||
for_ decs $ \declaration -> do
|
||||
name <- maybeM (throwEvalError $ NoNameError declaration) (declaredName declaration)
|
||||
declare (Declaration name) emptySpan Nothing
|
||||
declare (Declaration name) Default emptySpan Nothing
|
||||
(span, _) <- do
|
||||
ref <- eval declaration
|
||||
subtermSpan <- get @Span
|
||||
@ -210,7 +212,7 @@ instance Evaluatable PublicFieldDefinition where
|
||||
propertyName <- maybeM (throwEvalError $ NoNameError publicFieldPropertyName) (declaredName publicFieldPropertyName)
|
||||
|
||||
-- withScope instanceScope $ do
|
||||
declare (Declaration propertyName) span Nothing
|
||||
declare (Declaration propertyName) InstanceOf span Nothing
|
||||
slot <- lookupDeclaration (Declaration propertyName)
|
||||
value <- eval publicFieldValue
|
||||
assign slot value
|
||||
@ -258,7 +260,7 @@ instance Evaluatable Class where
|
||||
current = (Lexical, ) <$> pure (pure currentScope')
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) span (Just classScope)
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
|
||||
let frameEdges = Map.singleton Superclass (Map.fromList (catMaybes superScopes))
|
||||
classFrame <- newFrame classScope frameEdges
|
||||
@ -351,7 +353,8 @@ instance Evaluatable TypeAlias where
|
||||
|
||||
span <- ask @Span
|
||||
assocScope <- associatedScope (Declaration kindName)
|
||||
declare (Declaration name) span assocScope
|
||||
-- TODO: Should we consider a special Relation for `TypeAlias`?
|
||||
declare (Declaration name) Default span assocScope
|
||||
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
kindSlot <- lookupDeclaration (Declaration kindName)
|
||||
|
@ -638,6 +638,7 @@ instance Evaluatable New where
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
classVal <- deref slot
|
||||
classFrame <- maybeM (throwEvalError $ ScopedEnvError classVal) =<< scopedEnvironment classVal
|
||||
|
||||
objectFrame <- newFrame objectScope (Map.singleton Superclass $ Map.singleton assocScope classFrame)
|
||||
objectVal <- object objectFrame
|
||||
|
||||
|
@ -151,7 +151,7 @@ instance Evaluatable Let where
|
||||
assocScope <- associatedScope (Declaration valueName)
|
||||
|
||||
_ <- withLexicalScopeAndFrame $ do
|
||||
declare (Declaration name) letSpan assocScope
|
||||
declare (Declaration name) Default letSpan assocScope
|
||||
letVal <- eval letValue
|
||||
slot <- lookupDeclaration (Declaration name)
|
||||
assign slot letVal
|
||||
|
@ -85,7 +85,7 @@ instance Evaluatable QualifiedImport where
|
||||
alias <- maybeM (throwEvalError $ NoNameError aliasTerm) (declaredName aliasTerm)
|
||||
span <- ask @Span
|
||||
scopeAddress <- newScope mempty
|
||||
declare (Declaration alias) span (Just scopeAddress)
|
||||
declare (Declaration alias) Default span (Just scopeAddress)
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
|
||||
withScope scopeAddress $ do
|
||||
|
@ -148,7 +148,7 @@ instance Evaluatable Import where
|
||||
aliasFrame <- newFrame importScope (Map.singleton ScopeGraph.Import scopeMap)
|
||||
|
||||
-- Add declaration of the alias name to the current scope (within our current module).
|
||||
declare (Declaration aliasName) span (Just importScope)
|
||||
declare (Declaration aliasName) Default span (Just importScope)
|
||||
-- Retrieve the frame slot for the new declaration.
|
||||
aliasSlot <- lookupDeclaration (Declaration aliasName)
|
||||
assign aliasSlot =<< object aliasFrame
|
||||
@ -219,7 +219,7 @@ instance Evaluatable QualifiedImport where
|
||||
go ((name, modulePath) : namesAndPaths) = do
|
||||
span <- ask @Span
|
||||
scopeAddress <- newScope mempty
|
||||
declare (Declaration name) span (Just scopeAddress)
|
||||
declare (Declaration name) Default span (Just scopeAddress)
|
||||
aliasSlot <- lookupDeclaration (Declaration name)
|
||||
-- a.b.c
|
||||
withScope scopeAddress $
|
||||
@ -255,7 +255,7 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
span <- ask @Span
|
||||
scopeAddress <- newScope mempty
|
||||
alias <- maybeM (throwEvalError $ NoNameError aliasTerm) (declaredName aliasTerm)
|
||||
declare (Declaration alias) span (Just scopeAddress)
|
||||
declare (Declaration alias) Default span (Just scopeAddress)
|
||||
objFrame <- newFrame scopeAddress mempty
|
||||
val <- object objFrame
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
|
@ -221,7 +221,7 @@ instance Evaluatable Class where
|
||||
current = (Lexical, ) <$> pure (pure currentScope')
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) span (Just classScope)
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
|
||||
let frameEdges = Map.singleton Superclass (Map.fromList (catMaybes superScopes))
|
||||
childFrame <- newFrame classScope frameEdges
|
||||
@ -274,7 +274,7 @@ instance Evaluatable Module where
|
||||
Nothing -> do
|
||||
let edges = Map.singleton Lexical [ currentScope' ]
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) span (Just classScope)
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
|
||||
currentFrame' <- currentFrame
|
||||
let frameEdges = Map.singleton Lexical (Map.singleton currentScope' currentFrame')
|
||||
@ -350,7 +350,7 @@ instance Evaluatable Assignment where
|
||||
lhsName <- maybeM (throwEvalError $ NoNameError assignmentTarget) (declaredName assignmentTarget)
|
||||
maybeSlot <- maybeLookupDeclaration (Declaration lhsName)
|
||||
assignmentSpan <- ask @Span
|
||||
maybe (declare (Declaration lhsName) assignmentSpan Nothing) (const (pure ())) maybeSlot
|
||||
maybe (declare (Declaration lhsName) Default assignmentSpan Nothing) (const (pure ())) maybeSlot
|
||||
|
||||
lhs <- ref assignmentTarget
|
||||
rhs <- eval assignmentValue
|
||||
|
@ -98,7 +98,8 @@ instance Evaluatable RequiredParameter where
|
||||
eval eval ref RequiredParameter{..} = do
|
||||
name <- maybeM (throwEvalError $ NoNameError requiredParameterSubject) (declaredName requiredParameterSubject)
|
||||
span <- ask @Span
|
||||
declare (Declaration name) span Nothing
|
||||
-- TODO: Should we specify function parameters with a special Relation?
|
||||
declare (Declaration name) Default span Nothing
|
||||
|
||||
lhs <- ref requiredParameterSubject
|
||||
rhs <- eval requiredParameterValue
|
||||
|
@ -31,7 +31,7 @@ instance Evaluatable JavaScriptRequire where
|
||||
Just alias -> do
|
||||
span <- ask @Span
|
||||
importScope <- newScope (Map.singleton ScopeGraph.Import [ moduleScope ])
|
||||
declare (Declaration alias) span (Just importScope)
|
||||
declare (Declaration alias) Default span (Just importScope)
|
||||
let scopeMap = Map.singleton moduleScope moduleFrame
|
||||
aliasFrame <- newFrame importScope (Map.singleton ScopeGraph.Import scopeMap)
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
|
@ -68,7 +68,7 @@ instance Evaluatable QualifiedAliasedImport where
|
||||
aliasFrame <- newFrame importScope (Map.singleton ScopeGraph.Import scopeMap)
|
||||
|
||||
alias <- maybeM (throwEvalError $ NoNameError aliasTerm) (declaredName aliasTerm)
|
||||
declare (Declaration alias) span (Just importScope)
|
||||
declare (Declaration alias) Default span (Just importScope)
|
||||
aliasSlot <- lookupDeclaration (Declaration alias)
|
||||
assign aliasSlot =<< object aliasFrame
|
||||
|
||||
@ -159,7 +159,7 @@ instance Evaluatable DefaultExport where
|
||||
withScopeAndFrame exportFrame $ do
|
||||
valueRef <- eval term
|
||||
let declaration = Declaration $ Name.name "__default"
|
||||
declare declaration exportSpan Nothing
|
||||
declare declaration Default exportSpan Nothing
|
||||
defaultSlot <- lookupDeclaration declaration
|
||||
assign defaultSlot valueRef
|
||||
|
||||
@ -598,7 +598,7 @@ declareModule eval identifier statements = do
|
||||
Nothing -> do
|
||||
let edges = Map.singleton Lexical [ currentScope' ]
|
||||
childScope <- newScope edges
|
||||
declare (Declaration name) span (Just childScope)
|
||||
declare (Declaration name) Default span (Just childScope)
|
||||
|
||||
currentFrame' <- currentFrame
|
||||
let frameEdges = Map.singleton Lexical (Map.singleton currentScope' currentFrame')
|
||||
@ -676,7 +676,7 @@ instance Evaluatable AbstractClass where
|
||||
current = (Lexical, ) <$> pure (pure currentScope')
|
||||
edges = Map.fromList (superclassEdges <> current)
|
||||
classScope <- newScope edges
|
||||
declare (Declaration name) span (Just classScope)
|
||||
declare (Declaration name) Default span (Just classScope)
|
||||
|
||||
let frameEdges = Map.singleton Superclass (Map.fromList (catMaybes superScopes))
|
||||
childFrame <- newFrame classScope frameEdges
|
||||
|
6
test/fixtures/typescript/analysis/class2.ts
vendored
6
test/fixtures/typescript/analysis/class2.ts
vendored
@ -1,10 +1,10 @@
|
||||
class Adder {
|
||||
class Adder<A> {
|
||||
summand: number;
|
||||
constructor(summand: number) {
|
||||
this.summand = summand;
|
||||
}
|
||||
add() {
|
||||
return 4 + this.summand;
|
||||
add<A>(foo: A) {
|
||||
return foo
|
||||
}
|
||||
}
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user