mirror of
https://github.com/github/semantic.git
synced 2024-12-14 17:31:48 +03:00
Merge branch 'heap-frames' of https://github.com/github/semantic into heap-frames
This commit is contained in:
commit
47c2dea759
@ -160,7 +160,7 @@ insertImportReference ref decl scopeAddress = do
|
||||
scopeGraph <- get
|
||||
scope <- lookupScope scopeAddress
|
||||
currentAddress <- currentScope
|
||||
newScope <- maybeM (throwScopeError LookupScopeError) (ScopeGraph.insertImportReference ref decl currentAddress scopeGraph scope)
|
||||
newScope <- maybeM (throwScopeError ImportReferenceError) (ScopeGraph.insertImportReference ref decl currentAddress scopeGraph scope)
|
||||
insertScope scopeAddress newScope
|
||||
|
||||
insertScope :: ( Member (State (ScopeGraph address)) sig
|
||||
@ -235,6 +235,7 @@ throwScopeError = throwBaseError
|
||||
data ScopeError address return where
|
||||
ScopeError :: Declaration -> Span -> ScopeError address (Slot address)
|
||||
LookupScopeError :: ScopeError address (Scope address)
|
||||
ImportReferenceError :: ScopeError address (Scope address)
|
||||
LookupPathError :: Declaration -> ScopeError address (ScopeGraph.Path address)
|
||||
LookupDeclarationScopeError :: Declaration -> ScopeError address address
|
||||
CurrentScopeError :: ScopeError address address
|
||||
|
@ -156,7 +156,7 @@ insertImportReference ref decl@Declaration{..} currentAddress g scope = go curre
|
||||
where
|
||||
go address path
|
||||
= modifyReferences scope . Map.insert ref . path . DPath decl . snd <$> lookupDeclaration unDeclaration address g
|
||||
<|> traverseEdges' Superclass <|> traverseEdges' Import <|> traverseEdges' Lexical
|
||||
<|> traverseEdges' Superclass <|> traverseEdges' Export <|> traverseEdges' Import <|> traverseEdges' Lexical
|
||||
where traverseEdges' edge = linksOfScope address g >>= Map.lookup edge >>= traverseEdges path go edge
|
||||
|
||||
lookupScopePath :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
|
||||
@ -165,7 +165,7 @@ lookupScopePath declaration currentAddress g = go currentAddress id
|
||||
go address path
|
||||
= path . DPath (Declaration declaration) . snd <$> lookupDeclaration declaration address g
|
||||
<|> path <$> lookupReference declaration address g
|
||||
<|> traverseEdges' Superclass <|> traverseEdges' Import <|> traverseEdges' Lexical
|
||||
<|> traverseEdges' Superclass <|> traverseEdges' Export <|> traverseEdges' Import <|> traverseEdges' Lexical
|
||||
where traverseEdges' edge = linksOfScope address g >>= Map.lookup edge >>= traverseEdges path go edge
|
||||
|
||||
modifyReferences :: Scope scopeAddress -> (Map Reference (Path scopeAddress) -> Map Reference (Path scopeAddress)) -> Scope scopeAddress
|
||||
|
@ -125,14 +125,18 @@ instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec
|
||||
instance Evaluatable QualifiedExportFrom where
|
||||
eval _ (QualifiedExportFrom importPath exportSymbols) = do
|
||||
modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions
|
||||
-- scopeGraph <- fst <$> require modulePath
|
||||
-- Look up addresses in importedEnv and insert the aliases with addresses into the exports.
|
||||
for_ exportSymbols $ \Alias{..} -> do
|
||||
-- TODO: Add an Alias Edge to resolve qualified export froms
|
||||
-- Scope 1 -> alias (bar, foo) -> Export 3 -> Export -> Scope 4
|
||||
pure ()
|
||||
-- let address = Env.lookup aliasValue importedBinds
|
||||
-- maybe (throwEvalError $ ExportError modulePath aliasValue) (export aliasValue aliasName . Just) address
|
||||
|
||||
((moduleScope, moduleFrame), _) <- require modulePath
|
||||
exportScope <- newScope (Map.singleton ScopeGraph.Import [ moduleScope ])
|
||||
exportFrame <- newFrame exportScope (Map.singleton ScopeGraph.Import (Map.singleton moduleScope moduleFrame))
|
||||
|
||||
withScopeAndFrame moduleFrame .
|
||||
for_ exportSymbols $ \Alias{..} -> do
|
||||
insertImportReference (Reference aliasName) (Declaration aliasValue) exportScope
|
||||
|
||||
insertExportEdge exportScope
|
||||
insertFrameLink ScopeGraph.Export (Map.singleton exportScope exportFrame)
|
||||
|
||||
rvalBox unit
|
||||
|
||||
newtype DefaultExport a = DefaultExport { defaultExport :: a }
|
||||
|
@ -447,6 +447,7 @@ resumingScopeError :: ( Carrier sig m
|
||||
-> Evaluator term address value m a
|
||||
resumingScopeError = runScopeErrorWith (\ baseError -> traceError "ScopeError" baseError *> case baseErrorException baseError of
|
||||
ScopeError _ _ -> pure hole
|
||||
ImportReferenceError -> pure hole
|
||||
LookupScopeError -> pure hole
|
||||
LookupPathError _ -> pure hole
|
||||
CurrentScopeError -> pure hole
|
||||
|
@ -23,6 +23,13 @@ import SpecHelpers
|
||||
spec :: TaskConfig -> Spec
|
||||
spec config = parallel $ do
|
||||
describe "TypeScript" $ do
|
||||
it "qualified export from" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main6.ts", "baz.ts", "foo.ts"]
|
||||
case ModuleTable.lookup "main6.ts" <$> res of
|
||||
Right (Just (Module _ (scopeAndFrame, _) :| [])) -> do
|
||||
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "imports with aliased symbols" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main.ts", "foo.ts", "a.ts", "foo/b.ts"]
|
||||
case ModuleTable.lookup "main.ts" <$> res of
|
||||
|
1
test/fixtures/typescript/analysis/baz.ts
vendored
Normal file
1
test/fixtures/typescript/analysis/baz.ts
vendored
Normal file
@ -0,0 +1 @@
|
||||
export { foo } from "./foo"
|
3
test/fixtures/typescript/analysis/main6.ts
vendored
Normal file
3
test/fixtures/typescript/analysis/main6.ts
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
import { foo } from "./baz"
|
||||
|
||||
foo()
|
Loading…
Reference in New Issue
Block a user