{-# LANGUAGE CPP #-}
module Data.Graph.Inductive.Graph (
Node,LNode,UNode,
Edge,LEdge,UEdge,
Adj,Context,MContext,Decomp,GDecomp,UContext,UDecomp,
Path,LPath(..),UPath,
Graph(..),
DynGraph(..),
order,
size,
ufold,gmap,nmap,emap,nemap,
nodes,edges,toEdge,edgeLabel,toLEdge,newNodes,gelem,
insNode,insEdge,delNode,delEdge,delLEdge,delAllLEdge,
insNodes,insEdges,delNodes,delEdges,
buildGr,mkUGraph,
gfiltermap,nfilter,labnfilter,labfilter,subgraph,
context,lab,neighbors,lneighbors,
suc,pre,lsuc,lpre,
out,inn,outdeg,indeg,deg,
hasEdge,hasNeighbor,hasLEdge,hasNeighborAdj,
equal,
node',lab',labNode',neighbors',lneighbors',
suc',pre',lpre',lsuc',
out',inn',outdeg',indeg',deg',
prettify,
prettyPrint,
OrdGr(..)
) where
import Control.Arrow (first)
import Data.Function (on)
import qualified Data.IntSet as IntSet
import Data.List (delete, foldl', groupBy, sort, sortBy, (\\))
import Data.Maybe (fromMaybe, isJust)
#if __GLASGOW_HASKELL__ < 710
import Data.Monoid (mappend)
#endif
type Node = Int
type LNode a = (Node,a)
type UNode = LNode ()
type Edge = (Node,Node)
type LEdge b = (Node,Node,b)
type UEdge = LEdge ()
type Path = [Node]
newtype LPath a = LP { unLPath :: [LNode a] }
instance (Show a) => Show (LPath a) where
show (LP xs) = show xs
instance (Eq a) => Eq (LPath a) where
(LP []) == (LP []) = True
(LP ((_,x):_)) == (LP ((_,y):_)) = x==y
(LP _) == (LP _) = False
instance (Ord a) => Ord (LPath a) where
compare (LP []) (LP []) = EQ
compare (LP ((_,x):_)) (LP ((_,y):_)) = compare x y
compare _ _ = error "LPath: cannot compare two empty paths"
type UPath = [UNode]
type Adj b = [(b,Node)]
type Context a b = (Adj b,Node,a,Adj b)
type MContext a b = Maybe (Context a b)
type Decomp g a b = (MContext a b,g a b)
type GDecomp g a b = (Context a b,g a b)
type UContext = ([Node],Node,[Node])
type UDecomp g = (Maybe UContext,g)
class Graph gr where
{-# MINIMAL empty, isEmpty, match, mkGraph, labNodes #-}
empty :: gr a b
isEmpty :: gr a b -> Bool
match :: Node -> gr a b -> Decomp gr a b
mkGraph :: [LNode a] -> [LEdge b] -> gr a b
labNodes :: gr a b -> [LNode a]
matchAny :: gr a b -> GDecomp gr a b
matchAny g = case labNodes g of
[] -> error "Match Exception, Empty Graph"
(v,_):_ -> (c,g')
where
(Just c,g') = match v g
noNodes :: gr a b -> Int
noNodes = length . labNodes
nodeRange :: gr a b -> (Node,Node)
nodeRange g
| isEmpty g = error "nodeRange of empty graph"
| otherwise = (minimum vs, maximum vs)
where
vs = nodes g
labEdges :: gr a b -> [LEdge b]
labEdges = ufold (\(_,v,_,s)->(map (\(l,w)->(v,w,l)) s ++)) []
class (Graph gr) => DynGraph gr where
(&) :: Context a b -> gr a b -> gr a b
order :: (Graph gr) => gr a b -> Int
order = noNodes
size :: (Graph gr) => gr a b -> Int
size = length . labEdges
ufold :: (Graph gr) => (Context a b -> c -> c) -> c -> gr a b -> c
ufold f u g
| isEmpty g = u
| otherwise = f c (ufold f u g')
where
(c,g') = matchAny g
gmap :: (DynGraph gr) => (Context a b -> Context c d) -> gr a b -> gr c d
gmap f = ufold (\c->(f c&)) empty
{-# NOINLINE [0] gmap #-}
nmap :: (DynGraph gr) => (a -> c) -> gr a b -> gr c b
nmap f = gmap (\(p,v,l,s)->(p,v,f l,s))
{-# NOINLINE [0] nmap #-}
emap :: (DynGraph gr) => (b -> c) -> gr a b -> gr a c
emap f = gmap (\(p,v,l,s)->(map1 f p,v,l,map1 f s))
where
map1 g = map (first g)
{-# NOINLINE [0] emap #-}
nemap :: (DynGraph gr) => (a -> c) -> (b -> d) -> gr a b -> gr c d
nemap fn fe = gmap (\(p,v,l,s) -> (fe' p,v,fn l,fe' s))
where
fe' = map (first fe)
{-# NOINLINE [0] nemap #-}
nodes :: (Graph gr) => gr a b -> [Node]
nodes = map fst . labNodes
edges :: (Graph gr) => gr a b -> [Edge]
edges = map toEdge . labEdges
toEdge :: LEdge b -> Edge
toEdge (v,w,_) = (v,w)
toLEdge :: Edge -> b -> LEdge b
toLEdge (v,w) l = (v,w,l)
edgeLabel :: LEdge b -> b
edgeLabel (_,_,l) = l
newNodes :: (Graph gr) => Int -> gr a b -> [Node]
newNodes i g
| isEmpty g = [0..i-1]
| otherwise = [n+1..n+i]
where
(_,n) = nodeRange g
gelem :: (Graph gr) => Node -> gr a b -> Bool
gelem v = isJust . fst . match v
insNode :: (DynGraph gr) => LNode a -> gr a b -> gr a b
insNode (v,l) = (([],v,l,[])&)
{-# NOINLINE [0] insNode #-}
insEdge :: (DynGraph gr) => LEdge b -> gr a b -> gr a b
insEdge (v,w,l) g = (pr,v,la,(l,w):su) & g'
where
(mcxt,g') = match v g
(pr,_,la,su) = fromMaybe
(error ("insEdge: cannot add edge from non-existent vertex " ++ show v))
mcxt
{-# NOINLINE [0] insEdge #-}
delNode :: (Graph gr) => Node -> gr a b -> gr a b
delNode v = delNodes [v]
delEdge :: (DynGraph gr) => Edge -> gr a b -> gr a b
delEdge (v,w) g = case match v g of
(Nothing,_) -> g
(Just (p,v',l,s),g') -> (p,v',l,filter ((/=w).snd) s) & g'
delLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b
delLEdge = delLEdgeBy delete
delAllLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b
delAllLEdge = delLEdgeBy (filter . (/=))
delLEdgeBy :: (DynGraph gr) => ((b,Node) -> Adj b -> Adj b)
-> LEdge b -> gr a b -> gr a b
delLEdgeBy f (v,w,b) g = case match v g of
(Nothing,_) -> g
(Just (p,v',l,s),g') -> (p,v',l,f (b,w) s) & g'
insNodes :: (DynGraph gr) => [LNode a] -> gr a b -> gr a b
insNodes vs g = foldl' (flip insNode) g vs
{-# INLINABLE insNodes #-}
insEdges :: (DynGraph gr) => [LEdge b] -> gr a b -> gr a b
insEdges es g = foldl' (flip insEdge) g es
{-# INLINABLE insEdges #-}
delNodes :: (Graph gr) => [Node] -> gr a b -> gr a b
delNodes vs g = foldl' (snd .: flip match) g vs
delEdges :: (DynGraph gr) => [Edge] -> gr a b -> gr a b
delEdges es g = foldl' (flip delEdge) g es
buildGr :: (DynGraph gr) => [Context a b] -> gr a b
buildGr = foldr (&) empty
mkUGraph :: (Graph gr) => [Node] -> [Edge] -> gr () ()
mkUGraph vs es = mkGraph (labUNodes vs) (labUEdges es)
where
labUEdges = map (`toLEdge` ())
labUNodes = map (flip (,) ())
gfiltermap :: DynGraph gr => (Context a b -> MContext c d) -> gr a b -> gr c d
gfiltermap f = ufold (maybe id (&) . f) empty
labnfilter :: Graph gr => (LNode a -> Bool) -> gr a b -> gr a b
labnfilter p gr = delNodes (map fst . filter (not . p) $ labNodes gr) gr
nfilter :: DynGraph gr => (Node -> Bool) -> gr a b -> gr a b
nfilter f = labnfilter (f . fst)
labfilter :: DynGraph gr => (a -> Bool) -> gr a b -> gr a b
labfilter f = labnfilter (f . snd)
subgraph :: DynGraph gr => [Node] -> gr a b -> gr a b
subgraph vs = let vs' = IntSet.fromList vs
in nfilter (`IntSet.member` vs')
context :: (Graph gr) => gr a b -> Node -> Context a b
context g v = fromMaybe (error ("Match Exception, Node: "++show v))
(fst (match v g))
lab :: (Graph gr) => gr a b -> Node -> Maybe a
lab g v = fmap lab' . fst $ match v g
neighbors :: (Graph gr) => gr a b -> Node -> [Node]
neighbors = map snd .: lneighbors
lneighbors :: (Graph gr) => gr a b -> Node -> Adj b
lneighbors = maybe [] lneighbors' .: mcontext
suc :: (Graph gr) => gr a b -> Node -> [Node]
suc = map snd .: context4l
pre :: (Graph gr) => gr a b -> Node -> [Node]
pre = map snd .: context1l
lsuc :: (Graph gr) => gr a b -> Node -> [(Node,b)]
lsuc = map flip2 .: context4l
lpre :: (Graph gr) => gr a b -> Node -> [(Node,b)]
lpre = map flip2 .: context1l
out :: (Graph gr) => gr a b -> Node -> [LEdge b]
out g v = map (\(l,w)->(v,w,l)) (context4l g v)
inn :: (Graph gr) => gr a b -> Node -> [LEdge b]
inn g v = map (\(l,w)->(w,v,l)) (context1l g v)
outdeg :: (Graph gr) => gr a b -> Node -> Int
outdeg = length .: context4l
indeg :: (Graph gr) => gr a b -> Node -> Int
indeg = length .: context1l
deg :: (Graph gr) => gr a b -> Node -> Int
deg = deg' .: context
node' :: Context a b -> Node
node' (_,v,_,_) = v
lab' :: Context a b -> a
lab' (_,_,l,_) = l
labNode' :: Context a b -> LNode a
labNode' (_,v,l,_) = (v,l)
neighbors' :: Context a b -> [Node]
neighbors' (p,_,_,s) = map snd p++map snd s
lneighbors' :: Context a b -> Adj b
lneighbors' (p,_,_,s) = p ++ s
suc' :: Context a b -> [Node]
suc' = map snd . context4l'
pre' :: Context a b -> [Node]
pre' = map snd . context1l'
lsuc' :: Context a b -> [(Node,b)]
lsuc' = map flip2 . context4l'
lpre' :: Context a b -> [(Node,b)]
lpre' = map flip2 . context1l'
out' :: Context a b -> [LEdge b]
out' c@(_,v,_,_) = map (\(l,w)->(v,w,l)) (context4l' c)
inn' :: Context a b -> [LEdge b]
inn' c@(_,v,_,_) = map (\(l,w)->(w,v,l)) (context1l' c)
outdeg' :: Context a b -> Int
outdeg' = length . context4l'
indeg' :: Context a b -> Int
indeg' = length . context1l'
deg' :: Context a b -> Int
deg' (p,_,_,s) = length p+length s
hasEdge :: Graph gr => gr a b -> Edge -> Bool
hasEdge gr (v,w) = w `elem` suc gr v
hasNeighbor :: Graph gr => gr a b -> Node -> Node -> Bool
hasNeighbor gr v w = w `elem` neighbors gr v
hasLEdge :: (Graph gr, Eq b) => gr a b -> LEdge b -> Bool
hasLEdge gr (v,w,l) = (w,l) `elem` lsuc gr v
hasNeighborAdj :: (Graph gr, Eq b) => gr a b -> Node -> (b,Node) -> Bool
hasNeighborAdj gr v a = a `elem` lneighbors gr v
slabNodes :: (Graph gr) => gr a b -> [LNode a]
slabNodes = sortBy (compare `on` fst) . labNodes
glabEdges :: (Graph gr) => gr a b -> [GroupEdges b]
glabEdges = map (GEs . groupLabels)
. groupBy ((==) `on` toEdge)
. sortBy (compare `on` toEdge)
. labEdges
where
groupLabels les = toLEdge (toEdge (head les)) (map edgeLabel les)
equal :: (Eq a,Eq b,Graph gr) => gr a b -> gr a b -> Bool
equal g g' = slabNodes g == slabNodes g' && glabEdges g == glabEdges g'
newtype GroupEdges b = GEs (LEdge [b])
deriving (Show, Read)
instance (Eq b) => Eq (GroupEdges b) where
(GEs (v1,w1,bs1)) == (GEs (v2,w2,bs2)) = v1 == v2
&& w1 == w2
&& eqLists bs1 bs2
eqLists :: (Eq a) => [a] -> [a] -> Bool
eqLists xs ys = null (xs \\ ys) && null (ys \\ xs)
(.:) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(.:) = (.) . (.)
flip2 :: (a,b) -> (b,a)
flip2 (x,y) = (y,x)
context1l :: (Graph gr) => gr a b -> Node -> Adj b
context1l = maybe [] context1l' .: mcontext
context4l :: (Graph gr) => gr a b -> Node -> Adj b
context4l = maybe [] context4l' .: mcontext
mcontext :: (Graph gr) => gr a b -> Node -> MContext a b
mcontext = fst .: flip match
context1l' :: Context a b -> Adj b
context1l' (p,v,_,s) = p++filter ((==v).snd) s
context4l' :: Context a b -> Adj b
context4l' (p,v,_,s) = s++filter ((==v).snd) p
prettify :: (DynGraph gr, Show a, Show b) => gr a b -> String
prettify g = foldr (showsContext . context g) id (nodes g) ""
where
showsContext (_,n,l,s) sg = shows n . (':':) . shows l
. showString "->" . shows s
. ('\n':) . sg
prettyPrint :: (DynGraph gr, Show a, Show b) => gr a b -> IO ()
prettyPrint = putStr . prettify
newtype OrdGr gr a b = OrdGr { unOrdGr :: gr a b }
deriving (Read,Show)
instance (Graph gr, Ord a, Ord b) => Eq (OrdGr gr a b) where
g1 == g2 = compare g1 g2 == EQ
instance (Graph gr, Ord a, Ord b) => Ord (OrdGr gr a b) where
compare (OrdGr g1) (OrdGr g2) =
(compare `on` sort . labNodes) g1 g2
`mappend` (compare `on` sort . labEdges) g1 g2