1
1
mirror of https://github.com/github/semantic.git synced 2024-12-27 00:44:57 +03:00
semantic/src/Data/Graph.hs

116 lines
4.2 KiB
Haskell
Raw Normal View History

{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
2018-05-11 19:07:05 +03:00
module Data.Graph
( Graph(..)
, overlay
, connect
, vertex
2018-05-11 19:21:49 +03:00
, Lower(..)
2018-05-11 19:10:27 +03:00
, simplify
, topologicalSort
2018-09-07 01:12:12 +03:00
, VertexTag(..)
, Edge(..)
, vertexList
, edgeList
2018-05-11 19:07:05 +03:00
) where
2018-09-07 01:12:12 +03:00
import Prologue
2018-05-11 19:07:05 +03:00
import qualified Algebra.Graph as G
import qualified Algebra.Graph.AdjacencyMap as A
2018-09-07 01:12:12 +03:00
import Algebra.Graph.Class (connect, overlay, vertex)
2018-05-11 19:09:21 +03:00
import qualified Algebra.Graph.Class as Class
import qualified Algebra.Graph.ToGraph as Class
import Control.Effect
2018-10-22 17:26:15 +03:00
import Control.Effect.State
2018-09-07 01:12:12 +03:00
import Data.Aeson
import qualified Data.Set as Set
import Semantic.Api.V1.CodeAnalysisPB
2018-05-11 19:07:05 +03:00
2018-05-11 19:12:23 +03:00
-- | An algebraic graph with 'Ord', 'Semigroup', and 'Monoid' instances.
newtype Graph vertex = Graph { unGraph :: G.Graph vertex }
deriving (Alternative, Applicative, Eq, Functor, Monad, Show, Class.Graph, NFData)
2018-05-11 19:10:27 +03:00
instance Ord t => Class.ToGraph (Graph t) where
type ToVertex (Graph t) = t
toGraph = Class.toGraph . unGraph
2018-05-11 19:10:27 +03:00
2018-05-11 19:12:05 +03:00
simplify :: Ord vertex => Graph vertex -> Graph vertex
2018-05-11 19:10:27 +03:00
simplify (Graph graph) = Graph (G.simplify graph)
2018-05-11 19:10:59 +03:00
2018-10-31 19:20:38 +03:00
-- | Sort a graphs vertices topologically. Specced in @Data.Graph.Spec@.
topologicalSort :: forall v . Ord v => Graph v -> [v]
topologicalSort = go . Class.toAdjacencyMap . G.transpose . unGraph
where go :: A.AdjacencyMap v -> [v]
go graph
= visitedOrder . fst
. run
. runState (Visited lowerBound [])
. traverse_ visit
. A.vertexList
$ graph
2019-03-04 20:00:19 +03:00
where visit :: (Member (State (Visited v)) sig, Carrier sig m) => v -> m ()
visit v = do
isMarked <- Set.member v . visitedVertices <$> get
if isMarked then
pure ()
else do
modify (extendVisited (Set.insert v))
traverse_ visit (Set.toList (A.postSet v graph))
modify (extendOrder (v :))
data Visited v = Visited { visitedVertices :: !(Set v), visitedOrder :: [v] }
extendVisited :: (Set v -> Set v) -> Visited v -> Visited v
extendVisited f (Visited a b) = Visited (f a) b
extendOrder :: ([v] -> [v]) -> Visited v -> Visited v
extendOrder f (Visited a b) = Visited a (f b)
2018-09-07 01:12:12 +03:00
vertexList :: Ord v => Graph v -> [v]
vertexList = G.vertexList . unGraph
edgeList :: Ord v => Graph v -> [Edge v]
edgeList = fmap Edge . G.edgeList . unGraph
-- Instances
2018-05-11 19:15:28 +03:00
instance Lower (Graph vertex) where
lowerBound = Class.empty
2018-05-11 19:12:05 +03:00
instance Semigroup (Graph vertex) where
(<>) = overlay
2018-05-11 19:11:03 +03:00
2018-05-11 19:12:05 +03:00
instance Monoid (Graph vertex) where
2018-05-11 19:11:03 +03:00
mempty = Class.empty
mappend = (<>)
2018-05-11 19:11:49 +03:00
2018-05-11 19:12:05 +03:00
instance Ord vertex => Ord (Graph vertex) where
2018-05-11 19:11:49 +03:00
compare (Graph G.Empty) (Graph G.Empty) = EQ
compare (Graph G.Empty) _ = LT
compare _ (Graph G.Empty) = GT
compare (Graph (G.Vertex a)) (Graph (G.Vertex b)) = compare a b
compare (Graph (G.Vertex _)) _ = LT
compare _ (Graph (G.Vertex _)) = GT
compare (Graph (G.Overlay a1 a2)) (Graph (G.Overlay b1 b2)) = (compare `on` Graph) a1 b1 <> (compare `on` Graph) a2 b2
compare (Graph (G.Overlay _ _)) _ = LT
compare _ (Graph (G.Overlay _ _)) = GT
compare (Graph (G.Connect a1 a2)) (Graph (G.Connect b1 b2)) = (compare `on` Graph) a1 b1 <> (compare `on` Graph) a2 b2
2018-05-11 19:22:11 +03:00
2018-09-07 01:12:12 +03:00
class VertexTag vertex where
uniqueTag :: vertex -> Int
instance VertexTag DiffTreeVertex where uniqueTag = fromIntegral . diffVertexId
instance VertexTag TermVertex where uniqueTag = fromIntegral . vertexId
2018-09-07 01:12:12 +03:00
instance (Ord vertex, ToJSON vertex, VertexTag vertex) => ToJSON (Graph vertex) where
toJSON (Graph graph) = object ["vertices" .= G.vertexList graph, "edges" .= (Edge <$> G.edgeList graph)]
toEncoding (Graph graph) = pairs ("vertices" .= G.vertexList graph <> "edges" .= (Edge <$> G.edgeList graph))
2018-09-07 01:12:12 +03:00
newtype Edge vertex = Edge (vertex, vertex)
2018-09-07 01:12:12 +03:00
instance (ToJSON vertex, VertexTag vertex) => ToJSON (Edge vertex) where
toJSON (Edge (a, b)) = object ["source" .= uniqueTag a, "target" .= uniqueTag b]
toEncoding (Edge (a, b)) = pairs ("source" .= uniqueTag a <> "target" .= uniqueTag b)