[Haskell-cafe] Possible FGL bug

Neil Brown nccb2 at kent.ac.uk
Wed Nov 25 06:28:04 EST 2009


It looks like a bug to me.  Can you show an exact list of nodes and 
edges that is causing mkGraph to fail?  Or is that what you have 
displayed, and I can't parse it properly?

Thanks,

Neil.

Ivan Lazar Miljenovic wrote:
> When developing my QuickCheck-2 test-suite for graphviz, I wrote the
> following Arbitrary instance for FGL graphs (which needs
> FlexibleInstances):
>
> ,----
> | instance (Graph g, Arbitrary n, Arbitrary e, Show n, Show e) => Arbitrary (g n e) where
> |   arbitrary = do ns <- liftM nub arbitrary
> |                  let nGen = elements ns
> |                  lns <- mapM makeLNode ns
> |                  trace ("Nodes: " ++ show lns) (return ())
> |                  les <- listOf $ makeLEdge nGen
> |                  trace ("Edges: " ++ show les) (return ())
> |                  return $ mkGraph lns les
> |     where
> |       makeLNode n = liftM ((,) n) arbitrary
> |       makeLEdge nGen = liftM3 (,,) nGen nGen arbitrary
> | 
> |   shrink gr = map (flip delNode gr) (nodes gr)
> `----
>
> However, when I try to run this, I occasionally get irrefutable pattern
> match failures as follows:
>
> ,----
> | *Data.GraphViz.Testing.Instances.FGL Data.Graph.Inductive.Tree> sample (arbitrary :: Gen (Gr Int Char))
> | 
> | 
> | 0:0->[]
> | 
> | 0:-2->[]
> | 1:0->[('\a',0)]
> | 2:0->[]
> | 
> | -4:-3->[('U',-3),('#',1)]
> | -3:3->[]
> | 1:-1->[('}',-3)]
> | 
> | -8:8->[]
> | -3:2->[]
> | -1:-5->[('\US',-3),('&',0)]
> | 0:5->[('F',-1),('p',4)]
> | 4:-1->[]
> | 
> | -2:8->[('\177',-2),('(',-2),('d',-2),('4',-2),('D',-2),('\US',-2),('d',-2),('u',-2)]
> | 
> | -16:11->[]
> | -2:-2->[]
> | 0:11->[('@',1)]
> | 1:13->[('u',11)]
> | 9:-11->[('\231',11)]
> | 11:12->[('\226',1)]
> | 16:15->[]
> | 
> | -10:2->[]
> | -4:8->[]
> | 1:30->[]
> | 26:26->[('<',1),('K',-4)]
> | 31:-21->[]
> | 
> | -35:51->[('@',-29)]
> | -29:21->[('\132',-11)]
> | -11:-31->[('j',61)]
> | -4:40->[('a',-29)]
> | 0:6->[('z',-35),('9',28),('\170',-11),('\SUB',28)]
> | 23:8->[('P',-29),('(',61),('\\',28)]
> | 28:60->[]
> | 61:44->[('q',61)]
> | *** Exception: Data/Graph/Inductive/Graph.hs:250:26-59: Irrefutable pattern failed for pattern (Data.Maybe.Just (pr, _, la, su), g')
> `----
>
> The actual error comes from the definition of insEdge:
>
> ,----
> | -- | Insert a 'LEdge' into the 'Graph'.
> | insEdge :: DynGraph gr => LEdge b -> gr a b -> gr a b
> | insEdge (v,w,l) g = (pr,v,la,(l,w):su) & g'
> |                     where (Just (pr,_,la,su),g') = match v g
> `----
>
> with the Graph instance for Tree-based graphs using this for its mkGraph
> method:
>
> ,----
> |   mkGraph vs es   = (insEdges' . insNodes vs) empty
> |         where
> |           insEdges' g = foldl' (flip insEdge) g es
> `----
>
> So, is this really a bug in FGL, or am I using mkGraph wrong?
>
> On another note, why doesn't the PatriciaTree graph type have a Show
> instance? :(
>
>   



More information about the Haskell-Cafe mailing list