Understanding fgl's gfiltermap

Hi all, While playing with the fgl library [1] (git rev. 71b66d6), I encountered a situation where the library behaved different from what I expected. I now wonder whether I should adjust my expectations, or whether fgl has a bug. What I want to do is filter out nodes and edges based on edge labels. For a specific edge label l, if a node has an incoming or outgoing edge l it can stay, otherwise I want to remove it from my graph. Likewise, any edge that doesn't have label l needs to be removed from my graph. I wrote a program to do this using gfiltermap, but I got the wrong graph as a result. During debugging, I found that gfiltermap behaved differently from what I would expect. Take the following program: ```haskell {-# LANGUAGE TupleSections #-} module Test where import Debug.Trace import Data.Graph.Inductive main :: IO () main = prettyPrint test test :: Gr () () test = gfiltermap (Just . traceShowId) testGraph where {- - ASCII art representation of the graph: - - 1 <-4<-- 2 - /\ -/| - \ / - \3\/_ -} testGraph = mkGraph testNodes testEdges where testNodes = map (,()) [1, 2, 3, 4] testEdges = [ (2, 4, ()) , (4, 1, ()) , (2, 3, ()) , (3, 1, ()) , (3, 2, ()) ] ``` This simple program just reconstructs the original graph, but prints the contexts in the process. When it's done, it pretty prints the resulting graph. The debug tracing + pretty printing gives the following output (in that order): ([((),3),((),4)],1,(),[]) ([((),3)],2,(),[((),3),((),4)]) ([],3,(),[]) ([],4,(),[]) 1:()->[] 2:()->[((),3),((),4)] 3:()->[((),1),((),2)] 4:()->[((),1)] The pretty-printed graph correctly shows that there is an edges going from node 4 to node 1. However, the traced output shows node 4 (last line of trace output) with no successors and no predecessors. I would expect nodes 1 and 2 to be included in that tuple as the successor and predecessor in that tuple. Note that these two representations of the same graph _are_ isomorphic. Despite the isomorphism, this makes implementing my graph filter significantly more clumsy than I would like it to be. So my question is: are my expectations from the library wrong, or is this a bug? - Jurriën [1] https://hackage.haskell.org/package/fgl

On 23 September 2016 at 18:09, J. Stutterheim
Hi all,
While playing with the fgl library [1] (git rev. 71b66d6), I encountered a situation where the library behaved different from what I expected. I now wonder whether I should adjust my expectations, or whether fgl has a bug.
What I want to do is filter out nodes and edges based on edge labels. For a specific edge label l, if a node has an incoming or outgoing edge l it can stay, otherwise I want to remove it from my graph. Likewise, any edge that doesn't have label l needs to be removed from my graph.
I wrote a program to do this using gfiltermap, but I got the wrong graph as a result. During debugging, I found that gfiltermap behaved differently from what I would expect. Take the following program:
```haskell {-# LANGUAGE TupleSections #-}
module Test where
import Debug.Trace import Data.Graph.Inductive
main :: IO () main = prettyPrint test
test :: Gr () () test = gfiltermap (Just . traceShowId) testGraph where {- - ASCII art representation of the graph: - - 1 <-4<-- 2 - /\ -/| - \ / - \3\/_ -} testGraph = mkGraph testNodes testEdges where testNodes = map (,()) [1, 2, 3, 4] testEdges = [ (2, 4, ()) , (4, 1, ()) , (2, 3, ()) , (3, 1, ()) , (3, 2, ()) ] ```
This simple program just reconstructs the original graph, but prints the contexts in the process. When it's done, it pretty prints the resulting graph. The debug tracing + pretty printing gives the following output (in that order):
([((),3),((),4)],1,(),[]) ([((),3)],2,(),[((),3),((),4)]) ([],3,(),[]) ([],4,(),[])
1:()->[] 2:()->[((),3),((),4)] 3:()->[((),1),((),2)] 4:()->[((),1)]
The pretty-printed graph correctly shows that there is an edges going from node 4 to node 1. However, the traced output shows node 4 (last line of trace output) with no successors and no predecessors. I would expect nodes 1 and 2 to be included in that tuple as the successor and predecessor in that tuple. Note that these two representations of the same graph _are_ isomorphic.
Despite the isomorphism, this makes implementing my graph filter significantly more clumsy than I would like it to be. So my question is: are my expectations from the library wrong, or is this a bug?
This is how gfiltermap works: it deconstructs the graph inductively using matchAny.
- Jurriën
[1] https://hackage.haskell.org/package/fgl _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com
participants (2)
-
Ivan Lazar Miljenovic
-
J. Stutterheim