{-# LANGUAGE MultiParamTypeClasses #-}
module Data.Graph.Inductive.Example(
genUNodes, genLNodes, labUEdges, noEdges,
a, b, c, e, loop, ab, abb, dag3, e3, cyc3, g3, g3b, dag4, d1, d3,
a', b', c', e', loop', ab', abb', dag3', e3', dag4', d1', d3',
ucycle, star, ucycleM, starM,
clr479, clr489, clr486, clr508, clr528, clr595, gr1, kin248, vor,
clr479', clr489', clr486', clr508', clr528', kin248', vor'
)where
import Data.Graph.Inductive.Graph
import Data.Graph.Inductive.PatriciaTree
import Data.Graph.Inductive.Monad
import Data.Graph.Inductive.Monad.IOArray
genUNodes :: Int -> [UNode]
genUNodes :: Node -> [UNode]
genUNodes Node
n = forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
n] (forall a. a -> [a]
repeat ())
genLNodes :: (Enum a) => a -> Int -> [LNode a]
genLNodes :: forall a. Enum a => a -> Node -> [LNode a]
genLNodes a
q Node
i = forall a. Node -> [a] -> [a]
take Node
i (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..] [a
q..])
labUEdges :: [Edge] -> [UEdge]
labUEdges :: [Edge] -> [UEdge]
labUEdges = forall a b. (a -> b) -> [a] -> [b]
map (\(Node
i,Node
j) -> (Node
i,Node
j,()))
noEdges :: [UEdge]
noEdges :: [UEdge]
noEdges = []
a,b,c,e,loop,ab,abb,dag3 :: Gr Char ()
e3 :: Gr () String
cyc3,g3,g3b :: Gr Char String
dag4 :: Gr Int ()
d1,d3 :: Gr Int Int
a :: Gr Char ()
a = ([],Node
1,Char
'a',[]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& forall (gr :: * -> * -> *) a b. Graph gr => gr a b
empty
b :: Gr Char ()
b = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
2] String
"ab") [UEdge]
noEdges
c :: Gr Char ()
c = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
3] String
"abc") [UEdge]
noEdges
e :: Gr Char ()
e = ([((),Node
1)],Node
2,Char
'b',[]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& Gr Char ()
a
e3 :: Gr () String
e3 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (Node -> [UNode]
genUNodes Node
2)
[(Node
1,Node
2,String
"a"),(Node
1,Node
2,String
"b"),(Node
1,Node
2,String
"a")]
loop :: Gr Char ()
loop = ([],Node
1,Char
'a',[((),Node
1)]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& forall (gr :: * -> * -> *) a b. Graph gr => gr a b
empty
ab :: Gr Char ()
ab = ([((),Node
1)],Node
2,Char
'b',[((),Node
1)]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& Gr Char ()
a
abb :: Gr Char ()
abb = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
2] String
"ab") ([Edge] -> [UEdge]
labUEdges [(Node
2,Node
2)])
cyc3 :: Gr Char String
cyc3 = forall (gr :: * -> * -> *) a b.
DynGraph gr =>
[Context a b] -> gr a b
buildGr
[([(String
"ca",Node
3)],Node
1,Char
'a',[(String
"ab",Node
2)]),
([],Node
2,Char
'b',[(String
"bc",Node
3)]),
([],Node
3,Char
'c',[])]
dag3 :: Gr Char ()
dag3 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
3] String
"abc") ([Edge] -> [UEdge]
labUEdges [(Node
1,Node
3)])
dag4 :: Gr Node ()
dag4 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
4) ([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
1,Node
4),(Node
2,Node
3),(Node
2,Node
4),(Node
4,Node
3)])
d1 :: Gr Node Node
d1 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
2) [(Node
1,Node
2,Node
1)]
d3 :: Gr Node Node
d3 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
3) [(Node
1,Node
2,Node
1),(Node
1,Node
3,Node
4),(Node
2,Node
3,Node
2)]
g3 :: Gr Char String
g3 = ([(String
"left",Node
2),(String
"up",Node
3)],Node
1,Char
'a',[(String
"right",Node
2)]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& (
([],Node
2,Char
'b',[(String
"down",Node
3)]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& (
([],Node
3,Char
'c',[]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& forall (gr :: * -> * -> *) a b. Graph gr => gr a b
empty ))
g3b :: Gr Char String
g3b = ([(String
"down",Node
2)], Node
3,Char
'c',[(String
"up",Node
1)]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& (
([(String
"right",Node
1)],Node
2,Char
'b',[(String
"left",Node
1)]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& (
([],Node
1,Char
'a',[]) forall (gr :: * -> * -> *) a b.
DynGraph gr =>
Context a b -> gr a b -> gr a b
& forall (gr :: * -> * -> *) a b. Graph gr => gr a b
empty ))
a',b',c',e',loop',ab',abb',dag3' :: IO (SGr Char ())
e3' :: IO (SGr () String)
dag4' :: IO (SGr Int ())
d1',d3' :: IO (SGr Int Int)
a' :: IO (SGr Char ())
a' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM [(Node
1,Char
'a')] [UEdge]
noEdges
b' :: IO (SGr Char ())
b' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
2] String
"ab") [UEdge]
noEdges
c' :: IO (SGr Char ())
c' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
3] String
"abc") [UEdge]
noEdges
e' :: IO (SGr Char ())
e' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
2] String
"ab") [(Node
1,Node
2,())]
e3' :: IO (SGr () String)
e3' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (Node -> [UNode]
genUNodes Node
2)
[(Node
1,Node
2,String
"a"),(Node
1,Node
2,String
"b"),(Node
1,Node
2,String
"a")]
loop' :: IO (SGr Char ())
loop' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM [(Node
1,Char
'a')] [(Node
1,Node
1,())]
ab' :: IO (SGr Char ())
ab' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
2] String
"ab")
[(Node
1,Node
2,()),(Node
2,Node
1,())]
abb' :: IO (SGr Char ())
abb' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
2] String
"ab") ([Edge] -> [UEdge]
labUEdges [(Node
2,Node
2)])
dag3' :: IO (SGr Char ())
dag3' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
3] String
"abc") ([Edge] -> [UEdge]
labUEdges [(Node
1,Node
3)])
dag4' :: IO (SGr Node ())
dag4' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
4) ([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
1,Node
4),(Node
2,Node
3),(Node
2,Node
4),(Node
4,Node
3)])
d1' :: IO (SGr Node Node)
d1' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
2) [(Node
1,Node
2,Node
1)]
d3' :: IO (SGr Node Node)
d3' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
3) [(Node
1,Node
2,Node
1),(Node
1,Node
3,Node
4),(Node
2,Node
3,Node
2)]
ucycle :: (Graph gr) => Int -> gr () ()
ucycle :: forall (gr :: * -> * -> *). Graph gr => Node -> gr () ()
ucycle Node
n = forall (gr :: * -> * -> *).
Graph gr =>
[Node] -> [Edge] -> gr () ()
mkUGraph [Node]
vs (forall a b. (a -> b) -> [a] -> [b]
map (\Node
v->(Node
v,Node
v forall a. Integral a => a -> a -> a
`mod` Node
nforall a. Num a => a -> a -> a
+Node
1)) [Node]
vs)
where vs :: [Node]
vs = [Node
1..Node
n]
star :: (Graph gr) => Int -> gr () ()
star :: forall (gr :: * -> * -> *). Graph gr => Node -> gr () ()
star Node
n = forall (gr :: * -> * -> *).
Graph gr =>
[Node] -> [Edge] -> gr () ()
mkUGraph [Node
1..Node
n] (forall a b. (a -> b) -> [a] -> [b]
map (\Node
v->(Node
1,Node
v)) [Node
2..Node
n])
ucycleM :: (GraphM m gr) => Int -> m (gr () ())
ucycleM :: forall (m :: * -> *) (gr :: * -> * -> *).
GraphM m gr =>
Node -> m (gr () ())
ucycleM Node
n = forall (m :: * -> *) (gr :: * -> * -> *).
GraphM m gr =>
[Node] -> [Edge] -> m (gr () ())
mkUGraphM [Node]
vs (forall a b. (a -> b) -> [a] -> [b]
map (\Node
v->(Node
v,Node
v forall a. Integral a => a -> a -> a
`mod` Node
nforall a. Num a => a -> a -> a
+Node
1)) [Node]
vs)
where vs :: [Node]
vs = [Node
1..Node
n]
starM :: (GraphM m gr) => Int -> m (gr () ())
starM :: forall (m :: * -> *) (gr :: * -> * -> *).
GraphM m gr =>
Node -> m (gr () ())
starM Node
n = forall (m :: * -> *) (gr :: * -> * -> *).
GraphM m gr =>
[Node] -> [Edge] -> m (gr () ())
mkUGraphM [Node
1..Node
n] (forall a b. (a -> b) -> [a] -> [b]
map (\Node
v->(Node
1,Node
v)) [Node
2..Node
n])
clr479,clr489 :: Gr Char ()
clr486 :: Gr String ()
clr508,clr528 :: Gr Char Int
clr595,gr1 :: Gr Int Int
kin248 :: Gr Int ()
vor :: Gr String Int
clr479 :: Gr Char ()
clr479 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Char
'u' Node
6)
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
1,Node
4),(Node
2,Node
5),(Node
3,Node
5),(Node
3,Node
6),(Node
4,Node
2),(Node
5,Node
4),(Node
6,Node
6)])
clr486 :: Gr String ()
clr486 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
9] [String
"shorts",String
"socks",String
"watch",String
"pants",String
"shoes",
String
"shirt",String
"belt",String
"tie",String
"jacket"])
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
4),(Node
1,Node
5),(Node
2,Node
5),(Node
4,Node
5),(Node
4,Node
7),(Node
6,Node
7),(Node
6,Node
8),(Node
7,Node
9),(Node
8,Node
9)])
clr489 :: Gr Char ()
clr489 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Char
'a' Node
8)
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
2,Node
3),(Node
2,Node
5),(Node
2,Node
6),(Node
3,Node
4),(Node
3,Node
7),(Node
4,Node
3),(Node
4,Node
8),
(Node
5,Node
1),(Node
5,Node
6),(Node
6,Node
7),(Node
7,Node
6),(Node
7,Node
8),(Node
8,Node
8)])
clr508 :: Gr Char Node
clr508 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Char
'a' Node
9)
[(Node
1,Node
2,Node
4),(Node
1,Node
8,Node
8),(Node
2,Node
3,Node
8),(Node
2,Node
8,Node
11),(Node
3,Node
4,Node
7),(Node
3,Node
6,Node
4),(Node
3,Node
9,Node
2),
(Node
4,Node
5,Node
9),(Node
4,Node
6,Node
14),(Node
5,Node
6,Node
10),(Node
6,Node
7,Node
2),(Node
7,Node
8,Node
1),(Node
7,Node
9,Node
6),(Node
8,Node
9,Node
7)]
clr528 :: Gr Char Node
clr528 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph [(Node
1,Char
's'),(Node
2,Char
'u'),(Node
3,Char
'v'),(Node
4,Char
'x'),(Node
5,Char
'y')]
[(Node
1,Node
2,Node
10),(Node
1,Node
4,Node
5),(Node
2,Node
3,Node
1),(Node
2,Node
4,Node
2),(Node
3,Node
5,Node
4),
(Node
4,Node
2,Node
3),(Node
4,Node
3,Node
9),(Node
4,Node
5,Node
2),(Node
5,Node
1,Node
7),(Node
5,Node
3,Node
6)]
clr595 :: Gr Node Node
clr595 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
6] [Node
1..Node
6])
[(Node
1,Node
2,Node
16),(Node
1,Node
3,Node
13),(Node
2,Node
3,Node
10),(Node
2,Node
4,Node
12),(Node
3,Node
2,Node
4),
(Node
3,Node
5,Node
14),(Node
4,Node
3,Node
9),(Node
4,Node
6,Node
20),(Node
5,Node
4,Node
7),(Node
5,Node
6,Node
4)]
gr1 :: Gr Node Node
gr1 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
10] [Node
1..Node
10])
[(Node
1,Node
2,Node
12),(Node
1,Node
3,Node
1),(Node
1,Node
4,Node
2),(Node
2,Node
3,Node
1),(Node
2,Node
5,Node
7),(Node
2,Node
6,Node
5),(Node
3,Node
6,Node
1),
(Node
3,Node
7,Node
7),(Node
4,Node
3,Node
3),(Node
4,Node
6,Node
2),(Node
4,Node
7,Node
5),(Node
5,Node
3,Node
2),(Node
5,Node
6,Node
3),(Node
5,Node
8,Node
3),
(Node
6,Node
7,Node
2),(Node
6,Node
8,Node
3),(Node
6,Node
9,Node
1),(Node
7,Node
9,Node
9),(Node
8,Node
9,Node
1),(Node
8,Node
10,Node
4),(Node
9,Node
10,Node
11)]
kin248 :: Gr Node ()
kin248 = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
10)
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
1,Node
4),(Node
1,Node
7),(Node
2,Node
4),(Node
2,Node
5),(Node
3,Node
4),(Node
3,Node
10),
(Node
4,Node
5),(Node
4,Node
8),(Node
5,Node
2),(Node
5,Node
3),(Node
6,Node
7),(Node
7,Node
6),(Node
7,Node
8),
(Node
8,Node
10),(Node
9,Node
9),(Node
9,Node
10),(Node
10,Node
8),(Node
10,Node
9)])
vor :: Gr String Node
vor = forall (gr :: * -> * -> *) a b.
Graph gr =>
[LNode a] -> [LEdge b] -> gr a b
mkGraph (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
8] [String
"A",String
"B",String
"C",String
"H1",String
"H2",String
"D",String
"E",String
"F"])
[(Node
1,Node
4,Node
3),(Node
2,Node
3,Node
3),(Node
2,Node
4,Node
3),(Node
4,Node
2,Node
4),(Node
4,Node
6,Node
2),
(Node
5,Node
2,Node
5),(Node
5,Node
3,Node
6),(Node
5,Node
7,Node
5),(Node
5,Node
8,Node
6),
(Node
6,Node
5,Node
3),(Node
6,Node
7,Node
2),(Node
7,Node
8,Node
3),(Node
8,Node
7,Node
3)]
clr479',clr489' :: IO (SGr Char ())
clr486' :: IO (SGr String ())
clr508',clr528' :: IO (SGr Char Int)
kin248' :: IO (SGr Int ())
vor' :: IO (SGr String Int)
clr479' :: IO (SGr Char ())
clr479' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Char
'u' Node
6)
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
1,Node
4),(Node
2,Node
5),(Node
3,Node
5),(Node
3,Node
6),(Node
4,Node
2),(Node
5,Node
4),(Node
6,Node
6)])
clr486' :: IO (SGr String ())
clr486' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
9] [String
"shorts",String
"socks",String
"watch",String
"pants",String
"shoes",
String
"shirt",String
"belt",String
"tie",String
"jacket"])
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
4),(Node
1,Node
5),(Node
2,Node
5),(Node
4,Node
5),(Node
4,Node
7),(Node
6,Node
7),(Node
6,Node
8),(Node
7,Node
9),(Node
8,Node
9)])
clr489' :: IO (SGr Char ())
clr489' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Char
'a' Node
8)
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
2,Node
3),(Node
2,Node
5),(Node
2,Node
6),(Node
3,Node
4),(Node
3,Node
7),(Node
4,Node
3),(Node
4,Node
8),
(Node
5,Node
1),(Node
5,Node
6),(Node
6,Node
7),(Node
7,Node
6),(Node
7,Node
8),(Node
8,Node
8)])
clr508' :: IO (SGr Char Node)
clr508' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Char
'a' Node
9)
[(Node
1,Node
2,Node
4),(Node
1,Node
8,Node
8),(Node
2,Node
3,Node
8),(Node
2,Node
8,Node
11),(Node
3,Node
4,Node
7),(Node
3,Node
6,Node
4),(Node
3,Node
9,Node
2),
(Node
4,Node
5,Node
9),(Node
4,Node
6,Node
14),(Node
5,Node
6,Node
10),(Node
6,Node
7,Node
2),(Node
7,Node
8,Node
1),(Node
7,Node
9,Node
6),(Node
8,Node
9,Node
7)]
clr528' :: IO (SGr Char Node)
clr528' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM [(Node
1,Char
's'),(Node
2,Char
'u'),(Node
3,Char
'v'),(Node
4,Char
'x'),(Node
5,Char
'y')]
[(Node
1,Node
2,Node
10),(Node
1,Node
4,Node
5),(Node
2,Node
3,Node
1),(Node
2,Node
4,Node
2),(Node
3,Node
5,Node
4),
(Node
4,Node
2,Node
3),(Node
4,Node
3,Node
9),(Node
4,Node
5,Node
2),(Node
5,Node
1,Node
7),(Node
5,Node
3,Node
6)]
kin248' :: IO (SGr Node ())
kin248' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a. Enum a => a -> Node -> [LNode a]
genLNodes Node
1 Node
10)
([Edge] -> [UEdge]
labUEdges [(Node
1,Node
2),(Node
1,Node
4),(Node
1,Node
7),(Node
2,Node
4),(Node
2,Node
5),(Node
3,Node
4),(Node
3,Node
10),
(Node
4,Node
5),(Node
4,Node
8),(Node
5,Node
2),(Node
5,Node
3),(Node
6,Node
7),(Node
7,Node
6),(Node
7,Node
8),
(Node
8,Node
10),(Node
9,Node
9),(Node
9,Node
10),(Node
10,Node
8),(Node
10,Node
9)])
vor' :: IO (SGr String Node)
vor' = forall (m :: * -> *) (gr :: * -> * -> *) a b.
GraphM m gr =>
[LNode a] -> [LEdge b] -> m (gr a b)
mkGraphM (forall a b. [a] -> [b] -> [(a, b)]
zip [Node
1..Node
8] [String
"A",String
"B",String
"C",String
"H1",String
"H2",String
"D",String
"E",String
"F"])
[(Node
1,Node
4,Node
3),(Node
2,Node
3,Node
3),(Node
2,Node
4,Node
3),(Node
4,Node
2,Node
4),(Node
4,Node
6,Node
2),
(Node
5,Node
2,Node
5),(Node
5,Node
3,Node
6),(Node
5,Node
7,Node
5),(Node
5,Node
8,Node
6),
(Node
6,Node
5,Node
3),(Node
6,Node
7,Node
2),(Node
7,Node
8,Node
3),(Node
8,Node
7,Node
3)]