mirror of
https://github.com/github/semantic.git
synced 2024-12-22 22:31:36 +03:00
🔥 renderGraph.
This commit is contained in:
parent
cb9d795c53
commit
e723b07d1e
@ -2,7 +2,7 @@
|
||||
module Analysis.Abstract.Graph
|
||||
( Graph(..)
|
||||
, Vertex(..)
|
||||
, renderGraph
|
||||
, style
|
||||
, appendGraph
|
||||
, variableDefinition
|
||||
, moduleInclusion
|
||||
@ -38,10 +38,6 @@ data Vertex
|
||||
| Variable { vertexName :: ByteString }
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
-- | Render a 'Graph' to a 'ByteString' in DOT notation.
|
||||
renderGraph :: Graph Vertex -> ByteString
|
||||
renderGraph = export style
|
||||
|
||||
style :: Style Vertex ByteString
|
||||
style = (defaultStyle vertexName)
|
||||
{ vertexAttributes = vertexAttributes
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE GADTs, TypeOperators #-}
|
||||
module Semantic.Graph where
|
||||
|
||||
import Algebra.Graph.Export.Dot
|
||||
import Analysis.Abstract.Evaluating
|
||||
import Analysis.Abstract.Graph
|
||||
import Control.Monad.Effect.Trace
|
||||
@ -39,7 +40,7 @@ graph graphType renderer project
|
||||
CallGraph -> graphingTerms
|
||||
analyze runGraphAnalysis (evaluatePackageWith graphingModules (withTermSpans . graphingLoadErrors . analyzeTerm) package) >>= extractGraph >>= case renderer of
|
||||
JSONGraphRenderer -> pure . toOutput
|
||||
DOTGraphRenderer -> pure . renderGraph
|
||||
DOTGraphRenderer -> pure . export style
|
||||
where extractGraph result = case result of
|
||||
(Right ((_, graph), _), _) -> pure graph
|
||||
_ -> Task.throwError (toException (Exc.ErrorCall ("graphImports: import graph rendering failed " <> show result)))
|
||||
|
Loading…
Reference in New Issue
Block a user