Re: [Haskell-cafe] Possible FGL bug

2009-11-26 Thread Ivan Lazar Miljenovic

Well, I've made two changes, either of which might have done the
trick...

1) Sort the lists of nodes and edge;
2) Remove multiple edges (that is, have at most one edge f - t).

The latter requirement was because the property I was testing only
worked if there were no multiple edges.

Either way, it seems to work now without having any errors turn up, so
it seems to have done the trick...

David Menendez d...@zednenem.com writes:

 On Wed, Nov 25, 2009 at 11:02 AM, Neil Brown nc...@kent.ac.uk wrote:
 David Menendez wrote:

 From what I can tell, insEdge inserts an edge between two nodes which
 are already in the graph. The code is calling insEdge on
 arbitrarily-labeled nodes, which may not exist in the graph.


 That's what I thought initially, but in fact what it is doing is exactly
 what you suggest:

 Instead of picking arbitrary node labels, try selecting arbitrary
 elements from the list of node labels.

 That nGen = elements ns line assigns into nGen a random generator that
 will pick from ns, the list of nodes.

 You're right. I've tried this in ghci, and I'm not able to reproduce
 the error. I did get an exception from QuickCheck when it tried to
 call elements on an empty list, though.

 This code works fine for me:

 a :: Gen ([LNode Char], [LEdge Char], Gr Char Char)
 a = do
 NonEmpty ns' - arbitrary
 let ns = nub ns'
 let nGen = elements ns
 lns - mapM (\n - liftM ((,) n) arbitrary) ns
 les - listOf $ liftM3 (,,) nGen nGen arbitrary
 return (lns, les, mkGraph lns les)

 I suspect that there's no value to generating an arbitrary list of
 node IDs, as opposed to something like:

 ns - liftM (\(Positive n) - [0..n]) arbitrary

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread Neil Brown
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? :(

  


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread Ivan Lazar Miljenovic
(Sorry for sending this to you twice Neil, I forgot to CC -cafe).

Neil Brown nc...@kent.ac.uk writes:

 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?

That's what I was trying to do with the trace statements, but they
didn't seem to print anything... (hmmm, maybe if I put the trace
statements in the call to mkGraph itself).



 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? :(

   


-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread David Menendez
On Wed, Nov 25, 2009 at 6:28 AM, Neil Brown nc...@kent.ac.uk wrote:
 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?

From what I can tell, insEdge inserts an edge between two nodes which
are already in the graph. The code is calling insEdge on
arbitrarily-labeled nodes, which may not exist in the graph.

Instead of picking arbitrary node labels, try selecting arbitrary
elements from the list of node labels.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread Neil Brown

David Menendez wrote:

From what I can tell, insEdge inserts an edge between two nodes which
are already in the graph. The code is calling insEdge on
arbitrarily-labeled nodes, which may not exist in the graph.
  
That's what I thought initially, but in fact what it is doing is exactly 
what you suggest:

Instead of picking arbitrary node labels, try selecting arbitrary
elements from the list of node labels.

  
That nGen = elements ns line assigns into nGen a random generator that 
will pick from ns, the list of nodes.


Thanks,

Neil.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread David Menendez
On Wed, Nov 25, 2009 at 11:02 AM, Neil Brown nc...@kent.ac.uk wrote:
 David Menendez wrote:

 From what I can tell, insEdge inserts an edge between two nodes which
 are already in the graph. The code is calling insEdge on
 arbitrarily-labeled nodes, which may not exist in the graph.


 That's what I thought initially, but in fact what it is doing is exactly
 what you suggest:

 Instead of picking arbitrary node labels, try selecting arbitrary
 elements from the list of node labels.

 That nGen = elements ns line assigns into nGen a random generator that
 will pick from ns, the list of nodes.

You're right. I've tried this in ghci, and I'm not able to reproduce
the error. I did get an exception from QuickCheck when it tried to
call elements on an empty list, though.

This code works fine for me:

a :: Gen ([LNode Char], [LEdge Char], Gr Char Char)
a = do
NonEmpty ns' - arbitrary
let ns = nub ns'
let nGen = elements ns
lns - mapM (\n - liftM ((,) n) arbitrary) ns
les - listOf $ liftM3 (,,) nGen nGen arbitrary
return (lns, les, mkGraph lns les)

I suspect that there's no value to generating an arbitrary list of
node IDs, as opposed to something like:

ns - liftM (\(Positive n) - [0..n]) arbitrary

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe