mirror of
https://github.com/github/semantic.git
synced 2024-12-20 21:31:48 +03:00
Remove python aliases and add declaredAlias to Declarations
This commit is contained in:
parent
13ac7b4942
commit
ffb49d006b
@ -12,6 +12,9 @@ class Declarations syntax where
|
||||
declaredName :: syntax -> Maybe Name
|
||||
declaredName = const Nothing
|
||||
|
||||
declaredAlias :: syntax -> Maybe Name
|
||||
declaredAlias = const Nothing
|
||||
|
||||
class Declarations1 syntax where
|
||||
-- | Lift a function mapping each element to its declared name (if any) through a containing structure. This can be used to define the declared name for a composite piece of syntax in terms of the declared name of one of its components.
|
||||
--
|
||||
@ -19,12 +22,17 @@ class Declarations1 syntax where
|
||||
liftDeclaredName :: (a -> Maybe Name) -> syntax a -> Maybe Name
|
||||
liftDeclaredName _ _ = Nothing
|
||||
|
||||
liftDeclaredAlias :: (a -> Maybe Name) -> syntax a -> Maybe Name
|
||||
liftDeclaredAlias _ _ = Nothing
|
||||
|
||||
deriving instance Declarations1 syntax => Declarations (Term syntax ann)
|
||||
|
||||
instance (Declarations recur, Declarations1 syntax) => Declarations (TermF syntax ann recur) where
|
||||
declaredName = liftDeclaredName declaredName . termFOut
|
||||
declaredAlias = liftDeclaredAlias declaredAlias . termFOut
|
||||
|
||||
instance Apply Declarations1 fs => Declarations1 (Sum fs) where
|
||||
liftDeclaredName f = apply @Declarations1 (liftDeclaredName f)
|
||||
liftDeclaredAlias f = apply @Declarations1 (liftDeclaredAlias f)
|
||||
|
||||
instance Declarations1 []
|
||||
|
@ -182,6 +182,7 @@ instance FreeVariables1 Identifier where
|
||||
|
||||
instance Declarations1 Identifier where
|
||||
liftDeclaredName _ (Identifier x) = pure x
|
||||
liftDeclaredAlias _ (Identifier x) = pure x
|
||||
|
||||
-- | An accessibility modifier, e.g. private, public, protected, etc.
|
||||
newtype AccessibilityModifier a = AccessibilityModifier { contents :: Text }
|
||||
|
@ -419,9 +419,9 @@ import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliase
|
||||
-- `import a`
|
||||
plainImport = makeTerm <$> symbol DottedName <*> children (Python.Syntax.QualifiedImport . NonEmpty.map T.unpack <$> NonEmpty.some1 identifierSource)
|
||||
-- `from a import foo `
|
||||
importSymbol = makeNameAliasPair <$> aliasIdentifier <*> pure Nothing
|
||||
importSymbol = makeNameAliasPair <$> identifier
|
||||
-- `from a import foo as bar`
|
||||
aliasImportSymbol = symbol AliasedImport *> children (makeNameAliasPair <$> aliasIdentifier <*> (Just <$> aliasIdentifier))
|
||||
aliasImportSymbol = makeTerm <$> symbol AliasedImport <*> children (Python.Syntax.Alias <$> identifier <*> identifier)
|
||||
-- `from a import *`
|
||||
wildcard = symbol WildcardImport *> (name <$> source) $> []
|
||||
|
||||
@ -431,9 +431,7 @@ import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliase
|
||||
importPrefix = symbol ImportPrefix *> source
|
||||
identifierSource = (symbol Identifier <|> symbol Identifier') *> source
|
||||
|
||||
aliasIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source) <|> symbol DottedName *> (name <$> source)
|
||||
makeNameAliasPair from (Just alias) = Python.Syntax.Alias from alias
|
||||
makeNameAliasPair from Nothing = Python.Syntax.Alias from from
|
||||
makeNameAliasPair alias = Python.Syntax.Alias alias alias
|
||||
|
||||
assertStatement :: Assignment Term
|
||||
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call [] <$> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
|
@ -115,34 +115,40 @@ resolvePythonModules q = do
|
||||
modulePath <- resolve searchPaths
|
||||
maybeM (throwResolutionError $ NotFoundError path searchPaths Language.Python) modulePath
|
||||
|
||||
data Alias a = Alias { aliasValue :: a, aliasName :: a}
|
||||
deriving (Generic1, Diffable, Eq, Foldable, FreeVariables1, Functor, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Alias
|
||||
|
||||
instance Declarations1 Alias where
|
||||
liftDeclaredName declaredName = declaredName . aliasValue
|
||||
liftDeclaredAlias declaredAlias = declaredAlias . aliasName
|
||||
|
||||
toTuple :: Alias a -> (a, a)
|
||||
toTuple Alias{..} = (aliasValue, aliasName)
|
||||
|
||||
|
||||
-- | 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 :: QualifiedName, importSymbols :: ![Alias] }
|
||||
data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically Import
|
||||
|
||||
newtype FutureImport a = FutureImport { futureImportSymbols :: [Alias] }
|
||||
newtype FutureImport a = FutureImport { futureImportSymbols :: [a] }
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Message1, Named1, Ord, Show, ToJSONFields1, Traversable, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically FutureImport
|
||||
|
||||
instance Evaluatable FutureImport where
|
||||
|
||||
data Alias = Alias { aliasValue :: Name, aliasName :: Name }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show, Message, Named, ToJSON, NFData)
|
||||
|
||||
toTuple :: Alias -> (Name, Name)
|
||||
toTuple Alias{..} = (aliasValue, aliasName)
|
||||
|
||||
|
||||
-- from a import b
|
||||
instance Evaluatable Import where
|
||||
-- from . import moduleY -- aliasValue = moduleY, aliasName = moduleY
|
||||
-- from . import moduleY as moduleZ -- aliasValue = moduleY, aliasName = moduleZ
|
||||
-- This is a bit of a special case in the syntax as this actually behaves like a qualified relative import.
|
||||
eval _ _ (Import (RelativeQualifiedName n Nothing) [Alias{..}]) = do
|
||||
path <- NonEmpty.last <$> resolvePythonModules (RelativeQualifiedName n (Just (qualifiedName (formatName aliasValue :| []))))
|
||||
eval _ _ (Import (RelativeQualifiedName n Nothing) [aliasTerm]) = do
|
||||
aliasValue' <- maybeM (throwNoNameError aliasTerm) (declaredName aliasTerm)
|
||||
path <- NonEmpty.last <$> resolvePythonModules (RelativeQualifiedName n (Just (qualifiedName (formatName aliasValue' :| []))))
|
||||
((moduleScope, moduleFrame), _) <- require path
|
||||
|
||||
span <- ask @Span
|
||||
@ -154,6 +160,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).
|
||||
aliasName <- maybeM (throwNoNameError aliasTerm) (declaredAlias aliasTerm)
|
||||
declare (Declaration aliasName) Default span ScopeGraph.UnqualifiedImport (Just importScope)
|
||||
-- Retrieve the frame slot for the new declaration.
|
||||
aliasSlot <- lookupDeclaration (Declaration aliasName)
|
||||
@ -165,7 +172,7 @@ instance Evaluatable Import where
|
||||
-- from a import b as c
|
||||
-- from a import *
|
||||
-- from .moduleY import b
|
||||
eval _ _ (Import name xs) = do
|
||||
eval eval _ (Import name xs) = do
|
||||
modulePaths <- resolvePythonModules name
|
||||
|
||||
-- Eval parent modules first
|
||||
@ -181,8 +188,12 @@ instance Evaluatable Import where
|
||||
let scopeEdges = Map.singleton ScopeGraph.Import [ moduleScope ]
|
||||
scopeAddress <- newScope scopeEdges
|
||||
withScope moduleScope .
|
||||
for_ xs $ \Alias{..} ->
|
||||
insertImportReference (Reference aliasName) emptySpan ScopeGraph.Identifier (Declaration aliasValue) scopeAddress
|
||||
for_ xs $ \aliasTerm -> do
|
||||
aliasValue <- maybeM (throwNoNameError aliasTerm) (declaredName aliasTerm)
|
||||
aliasName <- maybeM (throwNoNameError aliasTerm) (declaredAlias aliasTerm)
|
||||
_ <- eval aliasTerm
|
||||
aliasSpan <- get @Span
|
||||
insertImportReference (Reference aliasName) aliasSpan ScopeGraph.Identifier (Declaration aliasValue) scopeAddress
|
||||
|
||||
let frameLinks = Map.singleton moduleScope moduleFrame
|
||||
frameAddress <- newFrame scopeAddress (Map.singleton ScopeGraph.Import frameLinks)
|
||||
|
@ -63,6 +63,7 @@ newtype TypeIdentifier a = TypeIdentifier { contents :: T.Text }
|
||||
|
||||
instance Declarations1 TypeIdentifier where
|
||||
liftDeclaredName _ (TypeIdentifier identifier) = Just (Evaluatable.name identifier)
|
||||
liftDeclaredAlias _ (TypeIdentifier identifier) = Just (Evaluatable.name identifier)
|
||||
|
||||
-- TODO: TypeIdentifier shouldn't evaluate to an address in the heap?
|
||||
instance Evaluatable TypeIdentifier where
|
||||
|
Loading…
Reference in New Issue
Block a user