$ ghc -O -prof --make TestGraph $ ./TestGraph +RTS -s -P -RTS TestGraph.stat with (testIG 50): 20,881,408 bytes maximum residency (62 sample(s)) %GC time 55.2% (56.0% elapsed) TestGraph.stat with (testG 50): 90,112 bytes maximum residency (1 sample(s)) %GC time 14.3% (21.2% elapsed) > module Main (main) where > import qualified Data.Graph as G > import qualified Data.Graph.Inductive as IG > import Data.Tree > import Data.Maybe > main :: IO () > main = do testIG 50 > -- testG 50 > testIG nn = do let gi = createIG nn > print $ length $ IG.edges gi > print $ igTestDFS gi > print $ igTestDFS' gi 1 > print $ igTestAdd gi > createIG :: Int -> IG.Gr String () > createIG nn = IG.mkGraph lnodes ledges > where nodes = [1 .. nn] > lnodes = zip nodes $ map show nodes > ledges = [(n1, n2, ()) | n1 <- nodes, n2 <- nodes] > igTestDFS g = length $ IG.dfs [1] g > igTestDFS' g sn = length sstr > where ns = IG.dfs [sn] g > sstr = concatMap (fromJust . (IG.lab g)) ns > igTestAdd g = igTestDFS' g'' (nn + 1) > where nn = IG.noNodes g > newNodes = [nn + 1 .. nn + nn] > lnodes = zip newNodes $ map show newNodes > ledges = [(n1, n2, ()) | n1 <- newNodes, n2 <- newNodes] > g' = IG.insNodes lnodes g > g'' = IG.insEdges ledges g' > type GG = (G.Graph, G.Vertex -> (String, Int, [Int]), Int -> Maybe G.Vertex) > testG nn = do let g = createG nn > print $ length $ G.edges $ fst3 g > print $ gTestDFS g > print $ gTestDFS' g 1 > print $ gTestAdd g > createG :: Int -> GG > createG nn = G.graphFromEdges edges > where edges = [(show k, k, [1 .. nn]) | k <- [1 .. nn]] > gTestDFS (g, fromVertex, toVertex) = length vs > where vs = flatten $ head $ G.dfs g [(fromJust $ toVertex 1)] > gTestDFS' (g, fromVertex, toVertex) sk = length sstr > where vs = flatten $ head $ G.dfs g [(fromJust $ toVertex sk)] > sstr = concatMap (fst3 . fromVertex) vs A little bit unfair but still performs well: > gTestAdd (g, fromVertex, _) = gTestDFS' gg (nn + 1) > where vertices = G.vertices g > nn = length vertices > edges = map fromVertex vertices > newks = [nn + 1 .. nn + nn] > edges' = [(show k, k, newks) | k <- newks] > -- edges' = map (\ (n, k, ks) -> (n, k + ki, map (ki +) ks)) edges > gg = G.graphFromEdges (edges ++ edges') > fst3 (x, _, _) = x > snd3 (_, y, _) = y