mirror of
https://github.com/github/semantic.git
synced 2024-11-28 01:47:01 +03:00
Fix up go imports for the new world
This commit is contained in:
parent
55fa6480d6
commit
a6eae9dc88
@ -12,6 +12,7 @@ module Data.Abstract.Evaluatable
|
||||
, evaluateModules
|
||||
, throwLoadError
|
||||
, resolve
|
||||
, listModulesInDir
|
||||
, require
|
||||
, load
|
||||
) where
|
||||
@ -108,6 +109,7 @@ instance Evaluatable [] where
|
||||
-- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists.
|
||||
eval = maybe unit (runApp . foldMap1 (App . subtermValue)) . nonEmpty
|
||||
|
||||
-- Resolve a list of module paths to a possible module table entry.
|
||||
resolve :: MonadEvaluatable term value m
|
||||
=> [ModuleName]
|
||||
-> m (Maybe ModuleName)
|
||||
@ -115,6 +117,11 @@ resolve names = do
|
||||
tbl <- askModuleTable
|
||||
pure $ find (`moduleTableMember` tbl) names
|
||||
|
||||
listModulesInDir :: MonadEvaluatable term value m
|
||||
=> FilePath
|
||||
-> m [ModuleName]
|
||||
listModulesInDir dir = moduleTableKeysForDir dir <$> askModuleTable
|
||||
|
||||
-- | Require/import another module by name and return it's environment and value.
|
||||
--
|
||||
-- Looks up the term's name in the cache of evaluated modules first, returns if found, otherwise loads/evaluates the module.
|
||||
|
@ -5,6 +5,7 @@ module Data.Abstract.ModuleTable
|
||||
, moduleTableLookup
|
||||
, moduleTableMember
|
||||
, moduleTableInsert
|
||||
, moduleTableKeysForDir
|
||||
, fromList
|
||||
) where
|
||||
|
||||
@ -12,6 +13,7 @@ import Data.Abstract.Module
|
||||
import qualified Data.Map as Map
|
||||
import Data.Semigroup
|
||||
import Prologue
|
||||
import System.FilePath.Posix
|
||||
import GHC.Generics (Generic1)
|
||||
|
||||
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModuleName a }
|
||||
@ -26,6 +28,9 @@ moduleTableMember k = Map.member k . unModuleTable
|
||||
moduleTableInsert :: ModuleName -> a -> ModuleTable a -> ModuleTable a
|
||||
moduleTableInsert k v = ModuleTable . Map.insert k v . unModuleTable
|
||||
|
||||
moduleTableKeysForDir :: FilePath -> ModuleTable a -> [ModuleName]
|
||||
moduleTableKeysForDir k = filter (\e -> k == takeDirectory e) . Map.keys . unModuleTable
|
||||
|
||||
|
||||
-- | Construct a 'ModuleTable' from a list of 'Module's.
|
||||
fromList :: [Module term] -> ModuleTable [Module term]
|
||||
|
@ -383,19 +383,17 @@ importDeclaration :: Assignment
|
||||
importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList))
|
||||
where
|
||||
-- `import . "lib/Math"`
|
||||
dotImport = inj <$> (makeImport <$> dot <*> importFromPath)
|
||||
-- dotImport = inj <$> (flip Go.Syntax.Import <$> (symbol Dot *> source *> pure []) <*> importFromPath)
|
||||
dotImport = inj <$> (flip Go.Syntax.Import <$> dot <*> importFromPath)
|
||||
-- `import _ "lib/Math"`
|
||||
sideEffectImport = inj <$> (flip Go.Syntax.SideEffectImport <$> underscore <*> importFromPath)
|
||||
-- `import m "lib/Math"`
|
||||
namedImport = inj <$> (flip Go.Syntax.QualifiedImport <$> packageIdentifier <*> importFromPath <*> pure [])
|
||||
namedImport = inj <$> (flip Go.Syntax.QualifiedImport <$> packageIdentifier <*> importFromPath)
|
||||
-- `import "lib/Math"`
|
||||
plainImport = inj <$> (symbol InterpretedStringLiteral >>= \loc -> do
|
||||
from <- importPath <$> source
|
||||
let alias = makeTerm loc (Syntax.Identifier (toName from)) -- Go takes `import "lib/Math"` and uses `Math` as the qualified name (e.g. `Math.Sin()`)
|
||||
Go.Syntax.QualifiedImport <$> pure from <*> pure alias <*> pure [])
|
||||
let alias = makeTerm loc (Syntax.Identifier (defaultAlias from)) -- Go takes `import "lib/Math"` and uses `Math` as the qualified name (e.g. `Math.Sin()`)
|
||||
Go.Syntax.QualifiedImport <$> pure from <*> pure alias)
|
||||
|
||||
makeImport dot path = Go.Syntax.Import path [] dot
|
||||
dot = makeTerm <$> symbol Dot <*> (Literal.TextElement <$> source)
|
||||
underscore = makeTerm <$> symbol BlankIdentifier <*> (Literal.TextElement <$> source)
|
||||
importSpec = makeTerm' <$> symbol ImportSpec <*> children (sideEffectImport <|> dotImport <|> namedImport <|> plainImport)
|
||||
|
@ -2,13 +2,12 @@
|
||||
module Language.Go.Syntax where
|
||||
|
||||
import Data.Abstract.Evaluatable hiding (Label)
|
||||
import Data.Abstract.Environment as Env
|
||||
import qualified Data.Abstract.Module as M
|
||||
import Diffing.Algorithm
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import qualified Data.ByteString as B
|
||||
import System.FilePath.Posix
|
||||
import Prologue
|
||||
import Prelude hiding (fail)
|
||||
|
||||
newtype ImportPath = ImportPath { unPath :: FilePath }
|
||||
deriving (Eq, Ord, Show)
|
||||
@ -17,21 +16,20 @@ importPath :: ByteString -> ImportPath
|
||||
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path)
|
||||
where stripQuotes = B.filter (`B.notElem` "\'\"")
|
||||
|
||||
toName :: ImportPath -> Name
|
||||
toName = BC.pack . unPath
|
||||
defaultAlias :: ImportPath -> Name
|
||||
defaultAlias = BC.pack . takeFileName . unPath
|
||||
|
||||
-- TODO: need to delineate between relative and absolute Go imports
|
||||
resolveGoImport :: MonadEvaluatable term value m => FilePath -> m [M.ModuleName]
|
||||
resolveGoImport relImportPath = do
|
||||
-- TODO: This is where we need to enumerator all files in the right dir.
|
||||
maybeModule <- resolve [relImportPath]
|
||||
maybe notFound (pure . pure) maybeModule
|
||||
where
|
||||
notFound = fail $ "Unable to resolve module import: " <> show relImportPath
|
||||
M.Module{..} <- currentModule
|
||||
let relRootDir = takeDirectory (makeRelative moduleRoot modulePath)
|
||||
listModulesInDir $ normalise (relRootDir </> normalise relImportPath)
|
||||
|
||||
-- | Import declarations (symbols are added directly to the calling environment).
|
||||
--
|
||||
-- If the list of symbols is empty copy everything to the calling environment.
|
||||
data Import a = Import { importFrom :: ImportPath, importSymbols :: ![(Name, Name)], importWildcardToken :: !a }
|
||||
data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
|
||||
instance Eq1 Import where liftEq = genericLiftEq
|
||||
@ -39,22 +37,18 @@ instance Ord1 Import where liftCompare = genericLiftCompare
|
||||
instance Show1 Import where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable Import where
|
||||
eval (Import (ImportPath name) xs _) = do
|
||||
eval (Import (ImportPath name) _) = do
|
||||
paths <- resolveGoImport name
|
||||
for_ paths $ \path -> do
|
||||
(importedEnv, _) <- isolate (require path)
|
||||
modifyEnv (mappend (renamed importedEnv))
|
||||
modifyEnv (mappend importedEnv)
|
||||
unit
|
||||
where
|
||||
renamed importedEnv
|
||||
| Prologue.null xs = importedEnv
|
||||
| otherwise = Env.overwrite xs importedEnv
|
||||
|
||||
|
||||
-- | Qualified Import declarations (symbols are qualified in calling environment).
|
||||
--
|
||||
-- If the list of symbols is empty copy and qualify everything to the calling environment.
|
||||
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a, qualifiedImportSymbols :: ![(Name, Name)]}
|
||||
data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a}
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1)
|
||||
|
||||
instance Eq1 QualifiedImport where liftEq = genericLiftEq
|
||||
@ -62,19 +56,16 @@ instance Ord1 QualifiedImport where liftCompare = genericLiftCompare
|
||||
instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
instance Evaluatable QualifiedImport where
|
||||
eval (QualifiedImport (ImportPath name) alias xs) = do
|
||||
eval (QualifiedImport (ImportPath name) aliasTerm) = do
|
||||
paths <- resolveGoImport name
|
||||
for_ paths $ \path -> do
|
||||
(importedEnv, _) <- isolate (require path)
|
||||
modifyEnv (mappend (Env.overwrite (renames importedEnv) importedEnv))
|
||||
unit
|
||||
where
|
||||
renames importedEnv
|
||||
| Prologue.null xs = fmap prepend (Env.names importedEnv)
|
||||
| otherwise = xs
|
||||
prefix = freeVariable (subterm alias)
|
||||
prepend n = (n, prefix <> n)
|
||||
let alias = freeVariable (subterm aliasTerm)
|
||||
void $ letrec' alias $ \addr -> do
|
||||
for_ paths $ \path -> do
|
||||
(importedEnv, _) <- isolate (require path)
|
||||
modifyEnv (mappend importedEnv)
|
||||
|
||||
makeNamespace alias addr []
|
||||
unit
|
||||
|
||||
-- | Side effect only imports (no symbols made available to the calling environment).
|
||||
data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a }
|
||||
|
2
test/fixtures/go/analysis/main1.go
vendored
2
test/fixtures/go/analysis/main1.go
vendored
@ -2,7 +2,7 @@ package main
|
||||
|
||||
import (
|
||||
f "./foo"
|
||||
_ "./bar"
|
||||
_ "./bar"
|
||||
)
|
||||
|
||||
func main() {
|
||||
|
Loading…
Reference in New Issue
Block a user