mirror of
https://github.com/github/semantic.git
synced 2024-12-20 21:31:48 +03:00
Little bit of naming clarity
This commit is contained in:
parent
7e63e150ed
commit
deb5961091
@ -18,7 +18,6 @@ module Analysis.Abstract.Graph
|
||||
import Algebra.Graph.Export.Dot hiding (vertexName)
|
||||
import Control.Abstract
|
||||
import Data.Abstract.Address
|
||||
import Data.Abstract.Name
|
||||
import Data.Abstract.Ref
|
||||
import Data.Abstract.Declarations
|
||||
import Data.Abstract.Module (Module (moduleInfo), ModuleInfo (..))
|
||||
@ -33,15 +32,15 @@ import qualified Data.Text.Encoding as T
|
||||
import Prologue hiding (project)
|
||||
|
||||
style :: Style Vertex Builder
|
||||
style = (defaultStyle (T.encodeUtf8Builder . vertexName))
|
||||
style = (defaultStyle (T.encodeUtf8Builder . vertexIdentifier))
|
||||
{ vertexAttributes = vertexAttributes
|
||||
, edgeAttributes = edgeAttributes
|
||||
}
|
||||
where vertexAttributes Package{} = [ "style" := "dashed", "shape" := "box" ]
|
||||
vertexAttributes Module{} = [ "style" := "dotted, rounded", "shape" := "box" ]
|
||||
vertexAttributes Variable{..} = [ "label" := T.encodeUtf8Builder (variableName <> " (Variable)"), "tooltip" := T.encodeUtf8Builder (showSpan variableSpan), "style" := "rounded", "shape" := "box" ]
|
||||
vertexAttributes Method{..} = [ "label" := T.encodeUtf8Builder (methodName <> " (Method)"), "tooltip" := T.encodeUtf8Builder (showSpan methodSpan) , "style" := "rounded", "shape" := "box" ]
|
||||
vertexAttributes Function{..} = [ "label" := T.encodeUtf8Builder (functionName <> " (Function)"), "tooltip" := T.encodeUtf8Builder (showSpan functionSpan), "style" := "rounded", "shape" := "box" ]
|
||||
vertexAttributes Variable{..} = [ "label" := T.encodeUtf8Builder (vertexName <> " (Variable)"), "tooltip" := T.encodeUtf8Builder (showSpan vertexSpan), "style" := "rounded", "shape" := "box" ]
|
||||
vertexAttributes Method{..} = [ "label" := T.encodeUtf8Builder (vertexName <> " (Method)"), "tooltip" := T.encodeUtf8Builder (showSpan vertexSpan) , "style" := "rounded", "shape" := "box" ]
|
||||
vertexAttributes Function{..} = [ "label" := T.encodeUtf8Builder (vertexName <> " (Function)"), "tooltip" := T.encodeUtf8Builder (showSpan vertexSpan), "style" := "rounded", "shape" := "box" ]
|
||||
edgeAttributes Package{} Module{} = [ "len" := "5.0", "style" := "dashed" ]
|
||||
edgeAttributes Module{} Module{} = [ "len" := "5.0", "label" := "imports" ]
|
||||
edgeAttributes Variable{} Module{} = [ "len" := "5.0", "color" := "blue", "label" := "refers to symbol defined in" ]
|
||||
@ -82,14 +81,12 @@ graphingTerms recur term@(In a syntax) = do
|
||||
Just (v@Method{}, _) -> recurWithContext v
|
||||
Just (v@Variable{..}, name) -> do
|
||||
variableDefinition v
|
||||
|
||||
maybeAddr <- TermEvaluator (lookupEnv name)
|
||||
case maybeAddr of
|
||||
Just a -> do
|
||||
defined <- gets (Map.lookup a)
|
||||
maybe (pure ()) (appendGraph . connect (vertex v) . vertex) defined
|
||||
_ -> pure ()
|
||||
|
||||
recur term
|
||||
_ -> recur term
|
||||
where
|
||||
|
@ -115,7 +115,7 @@ taggedGraphToAdjacencyList = accumToAdj . adjMapToAccum . adjacencyMap . toGraph
|
||||
accumToAdj (Acc vs es) = AdjacencyList (fromList vs) (fromList (toList es))
|
||||
|
||||
vertexToPB :: V.Vertex -> Tag -> Vertex
|
||||
vertexToPB s = Vertex t (V.vertexName s) where
|
||||
vertexToPB s = Vertex t (V.vertexIdentifier s) where
|
||||
t = case s of
|
||||
V.Package{} -> PACKAGE
|
||||
V.Module{} -> MODULE
|
||||
|
@ -6,7 +6,7 @@ module Data.Graph.Vertex
|
||||
, variableVertex
|
||||
, methodVertex
|
||||
, functionVertex
|
||||
, vertexName
|
||||
, vertexIdentifier
|
||||
, showSpan
|
||||
, VertexDeclaration (..)
|
||||
, VertexDeclaration' (..)
|
||||
@ -30,11 +30,11 @@ import Prologue hiding (packageName)
|
||||
|
||||
-- | A vertex of some specific type.
|
||||
data Vertex
|
||||
= Package { packageName :: Text }
|
||||
| Module { moduleName :: Text }
|
||||
| Variable { variableName :: Text, variableModuleName :: Text, variableSpan :: Span }
|
||||
| Method { methodName :: Text, methodModuleName :: Text, methodSpan :: Span }
|
||||
| Function { functionName :: Text, functionModuleName :: Text, functionSpan :: Span }
|
||||
= Package { vertexName :: Text }
|
||||
| Module { vertexName :: Text }
|
||||
| Variable { vertexName :: Text, vertexModuleName :: Text, vertexSpan :: Span }
|
||||
| Method { vertexName :: Text, vertexModuleName :: Text, vertexSpan :: Span }
|
||||
| Function { vertexName :: Text, vertexModuleName :: Text, vertexSpan :: Span }
|
||||
deriving (Eq, Ord, Show, Generic, Hashable)
|
||||
|
||||
packageVertex :: PackageInfo -> Vertex
|
||||
@ -53,14 +53,12 @@ functionVertex :: Text -> ModuleInfo -> Span -> Vertex
|
||||
functionVertex name ModuleInfo{..} = Function name (T.pack modulePath)
|
||||
|
||||
instance ToJSON Vertex where
|
||||
toJSON v = object [ "name" .= vertexName v, "type" .= vertexToType v ]
|
||||
toJSON v = object [ "name" .= vertexIdentifier v, "type" .= vertexToType v ]
|
||||
|
||||
vertexName :: Vertex -> Text
|
||||
vertexName Package{..} = packageName <> " (Package)"
|
||||
vertexName Module{..} = moduleName <> " (Module)"
|
||||
vertexName Variable{..} = variableModuleName <> "::" <> variableName <> " (Variable " <> showSpan variableSpan <> ")"
|
||||
vertexName Method{..} = methodModuleName <> "::" <> methodName <> " (Method " <> showSpan methodSpan <> ")"
|
||||
vertexName Function{..} = functionModuleName <> "::" <> functionName <> " (Function " <> showSpan functionSpan <> ")"
|
||||
vertexIdentifier :: Vertex -> Text
|
||||
vertexIdentifier v@Package{..} = vertexName <> " (" <> vertexToType v <> ")"
|
||||
vertexIdentifier v@Module{..} = vertexName <> " (" <> vertexToType v <> ")"
|
||||
vertexIdentifier v = vertexModuleName v <> "::" <> vertexName v <> " (" <> vertexToType v <> " " <> showSpan (vertexSpan v) <> ")"
|
||||
|
||||
showSpan :: Span -> Text
|
||||
showSpan (Span (Pos a b) (Pos c d)) = T.pack $
|
||||
@ -69,11 +67,11 @@ showSpan (Span (Pos a b) (Pos c d)) = T.pack $
|
||||
<> "[" <> show c <> ", " <> show d <> "]"
|
||||
|
||||
vertexToType :: Vertex -> Text
|
||||
vertexToType Package{} = "package"
|
||||
vertexToType Module{} = "module"
|
||||
vertexToType Variable{} = "variable"
|
||||
vertexToType Method{} = "method"
|
||||
vertexToType Function{} = "function"
|
||||
vertexToType Package{} = "Package"
|
||||
vertexToType Module{} = "Module"
|
||||
vertexToType Variable{} = "Variable"
|
||||
vertexToType Method{} = "Method"
|
||||
vertexToType Function{} = "Function"
|
||||
|
||||
instance Lower Vertex where
|
||||
lowerBound = Package ""
|
||||
|
Loading…
Reference in New Issue
Block a user