mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Fix up import conflicts
Co-Authored-By: Rick Winfrey <rick.winfrey@gmail.com>
This commit is contained in:
parent
7da4d50492
commit
22bdbdfafe
@ -5,8 +5,7 @@ module Control.Abstract (
|
||||
import Control.Abstract.Context as X
|
||||
import Control.Abstract.Evaluator as X
|
||||
import Control.Abstract.Heap as X
|
||||
import Control.Abstract.ScopeGraph as X hiding (ScopeError(..))
|
||||
import Control.Abstract.ScopeGraph as X (ScopeError)
|
||||
import Control.Abstract.ScopeGraph as X
|
||||
import Control.Abstract.Hole as X
|
||||
import Control.Abstract.Modules as X
|
||||
import Control.Abstract.Primitive as X
|
||||
|
@ -2,10 +2,7 @@
|
||||
module Control.Abstract.PythonPackage
|
||||
( runPythonPackaging, Strategy(..) ) where
|
||||
|
||||
import Control.Abstract.Evaluator (LoopControl, Return)
|
||||
import Control.Abstract.ScopeGraph (Allocator)
|
||||
import Control.Abstract.Heap (Deref)
|
||||
import Control.Abstract.Value
|
||||
import Control.Abstract
|
||||
import Control.Effect.Carrier
|
||||
import Control.Effect.Sum
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -19,7 +19,6 @@ module Data.Abstract.Evaluatable
|
||||
import Control.Abstract hiding (Load)
|
||||
import Control.Abstract.Context as X
|
||||
import Control.Abstract.Evaluator as X hiding (LoopControl(..), Return(..), catchLoopControl, runLoopControl, catchReturn, runReturn)
|
||||
import Control.Abstract.Heap as X hiding (runAddressError, runAddressErrorWith)
|
||||
import Control.Abstract.Modules as X (Modules, ModuleResult, ResolutionError(..), load, lookupModule, listModulesInDir, require, resolve, throwResolutionError)
|
||||
import Control.Abstract.Value as X hiding (Boolean(..), Function(..), While(..))
|
||||
import Data.Abstract.Declarations as X
|
||||
|
@ -76,7 +76,7 @@ lookup address (EPath label scope path) declaration heap = do
|
||||
|
||||
lookupDeclaration :: Ord address => Declaration -> ScopeGraph address -> Heap address address value -> Maybe (Address address)
|
||||
lookupDeclaration Declaration{..} scopeGraph heap = do
|
||||
path <- lookupScopePath name scopeGraph
|
||||
path <- lookupScopePath unDeclaration scopeGraph
|
||||
frameAddress <- lookupFrameAddress path heap
|
||||
pure (Address frameAddress (pathPosition path))
|
||||
|
||||
|
@ -113,7 +113,7 @@ reference ref decl@Declaration{..} g@ScopeGraph{..} = fromMaybe g $ do
|
||||
go currentAddress currentScope' currentAddress id
|
||||
where
|
||||
go currentAddress currentScope address path =
|
||||
case lookupDeclaration name address g of
|
||||
case lookupDeclaration unDeclaration address g of
|
||||
Just (_, index) ->
|
||||
let newScope = currentScope { references = Map.insert ref (path (DPath decl index)) (references currentScope) }
|
||||
in Just (g { graph = Map.insert currentAddress newScope graph })
|
||||
@ -132,7 +132,7 @@ insertImportReference ref decl@Declaration{..} g@ScopeGraph{..} scopeAddress sco
|
||||
go currentAddress (EPath Import scopeAddress)
|
||||
where
|
||||
go address path =
|
||||
case lookupDeclaration name address g of
|
||||
case lookupDeclaration unDeclaration address g of
|
||||
Just (_, index) ->
|
||||
Just $ scope { references = Map.insert ref (path (DPath decl index)) (references scope) }
|
||||
Nothing -> traverseEdges Import <|> traverseEdges Lexical
|
||||
@ -177,7 +177,7 @@ insertEdge label target g@ScopeGraph{..} = fromMaybe g $ do
|
||||
insertDeclarationScope :: Ord scopeAddress => Declaration -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
insertDeclarationScope decl@Declaration{..} address g@ScopeGraph{..} = fromMaybe g $ do
|
||||
declScope <- scopeOfDeclaration decl g
|
||||
(span, position) <- (fst . snd . fst &&& unPosition . snd) <$> lookupDeclaration name declScope g
|
||||
(span, position) <- (fst . snd . fst &&& unPosition . snd) <$> lookupDeclaration unDeclaration declScope g
|
||||
scope <- lookupScope declScope g
|
||||
pure $ g { graph = Map.insert declScope (scope { declarations = Seq.adjust (const (decl, (span, Just address))) position (declarations scope) }) graph }
|
||||
|
||||
@ -209,20 +209,20 @@ pathOfRef ref graph = do
|
||||
scopeOfDeclaration :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
|
||||
scopeOfDeclaration Declaration{..} g@ScopeGraph{..} = go (Map.keys graph)
|
||||
where
|
||||
go (scope : scopes') = fromMaybe (go scopes') $ lookupDeclaration name scope g >> pure (Just scope)
|
||||
go (scope : scopes') = fromMaybe (go scopes') $ lookupDeclaration unDeclaration scope g >> pure (Just scope)
|
||||
go [] = Nothing
|
||||
|
||||
-- | Returns the scope associated with a declaration (the child scope if any exists).
|
||||
associatedScope :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
|
||||
associatedScope Declaration{..} g@ScopeGraph{..} = go (Map.keys graph)
|
||||
where
|
||||
go (scope : scopes') = fromMaybe (go scopes') $ snd . snd . fst <$> lookupDeclaration name scope g
|
||||
go (scope : scopes') = fromMaybe (go scopes') $ snd . snd . fst <$> lookupDeclaration unDeclaration scope g
|
||||
go [] = Nothing
|
||||
|
||||
newtype Reference = Reference { name :: Name }
|
||||
newtype Reference = Reference { unReference :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
newtype Declaration = Declaration { name :: Name }
|
||||
newtype Declaration = Declaration { unDeclaration :: Name }
|
||||
deriving (Eq, Ord, Show, Generic, NFData)
|
||||
|
||||
-- | The type of edge from a scope to its parent scopes.
|
||||
|
@ -12,7 +12,7 @@ import qualified Data.Text as T
|
||||
import Diffing.Algorithm
|
||||
import Prologue hiding (Text)
|
||||
import Proto3.Suite.Class
|
||||
import Control.Abstract.ScopeGraph
|
||||
import Control.Abstract
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import qualified Data.Map.Strict as Map
|
||||
|
||||
|
@ -1,7 +1,6 @@
|
||||
module Analysis.Ruby.Spec (spec) where
|
||||
|
||||
import Data.Abstract.Environment as Env
|
||||
import Data.Abstract.Evaluatable
|
||||
import qualified Data.Abstract.ModuleTable as ModuleTable
|
||||
import Data.Abstract.Number as Number
|
||||
import Data.Abstract.Value.Concrete as Value
|
||||
@ -11,6 +10,7 @@ import Data.List.NonEmpty (NonEmpty(..))
|
||||
import Data.Sum
|
||||
import qualified Language.Ruby.Assignment as Ruby
|
||||
import qualified Data.Language as Language
|
||||
import Data.Abstract.Evaluatable
|
||||
|
||||
import SpecHelpers
|
||||
|
||||
|
@ -13,9 +13,10 @@ module SpecHelpers
|
||||
, Config
|
||||
, LogQueue
|
||||
, StatQueue
|
||||
, lookupDeclaration
|
||||
) where
|
||||
|
||||
import Control.Abstract
|
||||
import Control.Abstract hiding (lookupDeclaration)
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import qualified Data.Abstract.Heap as Heap
|
||||
import Control.Arrow ((&&&))
|
||||
|
Loading…
Reference in New Issue
Block a user