[Haskell-cafe] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Thomas DuBuisson
All,

The containers library has a somewhat primitive but certainly useful
Data.Graph library.  Building a graph with this library simultaneously
results in the lookup functions:

   m1 :: Vertex -> (node, key, [key])
   m2 :: key -> Maybe Vertex

(where 'key' is like FGL's 'label' but is assumed to be unique)

This is exactly what I wanted when building and analyzing a call graph
in FGL.  To that end, I started making a graph type that tracked label
to Node mappings, wrapping Data.Graph.Inductive.Gr,  and assuming the
labels are all unique.

The classes for such a graph actually aren't possible.  The ability to
build a mapping from a node's 'label' to the 'Node' requires extra
context (ex: Hashable, Ord, or at least Eq), but such context can not
be provided due to the typeclass construction.

Is there any chance we can change the Graph and DiaGraph classes to
expose the type variables 'a' and 'b'?

class Graph gr a b where ...
class (Graph gr) => DynGraph gr a b where ...

This would allow instances to provide the needed context:

instance (Hashable a, Hashable b) => Graph UniqueLabel a b where
  ...
  buildGraph = ... some use of containers libraries that
require context ...
  ...
lookupNode :: Hashable a => UniqueLabel a b -> a -> Node
-- etc


Cheers,
Thomas

P.S.  Please do educate me if I simply missed or misunderstood some
feature of FGL.

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


Re: [Haskell-cafe] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Ivan Lazar Miljenovic
On 24 November 2011 20:33, Thomas DuBuisson  wrote:
> All,
>
> The containers library has a somewhat primitive but certainly useful
> Data.Graph library.  Building a graph with this library simultaneously
> results in the lookup functions:
>
>   m1 :: Vertex -> (node, key, [key])
>   m2 :: key -> Maybe Vertex
>
> (where 'key' is like FGL's 'label' but is assumed to be unique)
>
> This is exactly what I wanted when building and analyzing a call graph
> in FGL.  To that end, I started making a graph type that tracked label
> to Node mappings, wrapping Data.Graph.Inductive.Gr,  and assuming the
> labels are all unique.
>
> The classes for such a graph actually aren't possible.  The ability to
> build a mapping from a node's 'label' to the 'Node' requires extra
> context (ex: Hashable, Ord, or at least Eq), but such context can not
> be provided due to the typeclass construction.
>
> Is there any chance we can change the Graph and DiaGraph classes to
> expose the type variables 'a' and 'b'?
>
>    class Graph gr a b where ...
>    class (Graph gr) => DynGraph gr a b where ...
>
> This would allow instances to provide the needed context:
>
>    instance (Hashable a, Hashable b) => Graph UniqueLabel a b where
>          ...
>          buildGraph = ... some use of containers libraries that
> require context ...
>          ...
>    lookupNode :: Hashable a => UniqueLabel a b -> a -> Node
>    -- etc
>
>
> Cheers,
> Thomas
>
> P.S.  Please do educate me if I simply missed or misunderstood some
> feature of FGL.

Well, there *is* the NodeMap module, but I haven't really used it so
I'm not sure if it does what you want.

We did start upon a version of FGL which had these type variables in
the class, but it got a little fiddly; the ability to have superclass
constraints should solve this but I haven't touched FGL for a while,
as I've been working on some other graph library code for planar
graphs, with the plan to take my experience from writing this library
into a "successor" to FGL.

However, my experience with designing this planar graph library has
led me to using abstract (i.e. non-exported constructor) ID types for
nodes and edges and finding them rather useful, but then I'm more
concerned about the _structure_ of the graph rather than the items
stored within it.  As such, I'd appreciate you explaining to me
(off-list is OK) why you want/need such a label -> node mapping so
that I can try and work out a way to incorporate such functionality.

-- 
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] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Ivan Lazar Miljenovic
On 24 November 2011 20:42, Ivan Lazar Miljenovic
 wrote:
> On 24 November 2011 20:33, Thomas DuBuisson  
> wrote:
>> All,
>>
>> The containers library has a somewhat primitive but certainly useful
>> Data.Graph library.  Building a graph with this library simultaneously
>> results in the lookup functions:
>>
>>   m1 :: Vertex -> (node, key, [key])
>>   m2 :: key -> Maybe Vertex
>>
>> (where 'key' is like FGL's 'label' but is assumed to be unique)
>>
>> This is exactly what I wanted when building and analyzing a call graph
>> in FGL.  To that end, I started making a graph type that tracked label
>> to Node mappings, wrapping Data.Graph.Inductive.Gr,  and assuming the
>> labels are all unique.
>>
>> The classes for such a graph actually aren't possible.  The ability to
>> build a mapping from a node's 'label' to the 'Node' requires extra
>> context (ex: Hashable, Ord, or at least Eq), but such context can not
>> be provided due to the typeclass construction.
>>
>> Is there any chance we can change the Graph and DiaGraph classes to
>> expose the type variables 'a' and 'b'?
>>
>>    class Graph gr a b where ...
>>    class (Graph gr) => DynGraph gr a b where ...
>>
>> This would allow instances to provide the needed context:
>>
>>    instance (Hashable a, Hashable b) => Graph UniqueLabel a b where
>>          ...
>>          buildGraph = ... some use of containers libraries that
>> require context ...
>>          ...
>>    lookupNode :: Hashable a => UniqueLabel a b -> a -> Node
>>    -- etc
>>
>>
>> Cheers,
>> Thomas
>>
>> P.S.  Please do educate me if I simply missed or misunderstood some
>> feature of FGL.
>
> Well, there *is* the NodeMap module, but I haven't really used it so
> I'm not sure if it does what you want.
>
> We did start upon a version of FGL which had these type variables in
> the class, but it got a little fiddly; the ability to have superclass
> constraints should solve this but I haven't touched FGL for a while,
> as I've been working on some other graph library code for planar
> graphs, with the plan to take my experience from writing this library
> into a "successor" to FGL.
>
> However, my experience with designing this planar graph library has
> led me to using abstract (i.e. non-exported constructor) ID types for
> nodes and edges and finding them rather useful, but then I'm more
> concerned about the _structure_ of the graph rather than the items
> stored within it.  As such, I'd appreciate you explaining to me
> (off-list is OK) why you want/need such a label -> node mapping so
> that I can try and work out a way to incorporate such functionality.

To be more clear: we wanted superclass constraints because we had the
main classes be of kind * with associated-types for the node and edge
labels (which could possibly just be `()'); but to be able to do
mapping over the nodes and edges we needed to be able to specify a
mapping from "(g a b)" to "g a b" (where g is of kind * -> * -> *).

-- 
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] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Thomas DuBuisson
My thinking on this was that something akin to NodeMap should be
_part_ of the graph structure.  This would be more convenient and
allow the graph and nodemap operations to apply to a single data
structure.

Instead of:

insMapNode_ :: (Ord a, DynGraph g) => NodeMap a -> a -> g a b -> g a b

You could have:

insMapNode_ :: (Ord a, DynGraph g) => a -> g a b -> g a b

The only think stopping us from making a product data type like this
is the inflexibility of the type classes, right?  Were we able to
define (&) to update the nodemap too then we could keep these to
structures in sync automatically instead of expecting the programmer
to keep them paired correctly.

Cheers,
Thomas

On Thu, Nov 24, 2011 at 1:42 AM, Ivan Lazar Miljenovic
 wrote:
> On 24 November 2011 20:33, Thomas DuBuisson  
> wrote:
>> All,
>>
>> The containers library has a somewhat primitive but certainly useful
>> Data.Graph library.  Building a graph with this library simultaneously
>> results in the lookup functions:
>>
>>   m1 :: Vertex -> (node, key, [key])
>>   m2 :: key -> Maybe Vertex
>>
>> (where 'key' is like FGL's 'label' but is assumed to be unique)
>>
>> This is exactly what I wanted when building and analyzing a call graph
>> in FGL.  To that end, I started making a graph type that tracked label
>> to Node mappings, wrapping Data.Graph.Inductive.Gr,  and assuming the
>> labels are all unique.
>>
>> The classes for such a graph actually aren't possible.  The ability to
>> build a mapping from a node's 'label' to the 'Node' requires extra
>> context (ex: Hashable, Ord, or at least Eq), but such context can not
>> be provided due to the typeclass construction.
>>
>> Is there any chance we can change the Graph and DiaGraph classes to
>> expose the type variables 'a' and 'b'?
>>
>>    class Graph gr a b where ...
>>    class (Graph gr) => DynGraph gr a b where ...
>>
>> This would allow instances to provide the needed context:
>>
>>    instance (Hashable a, Hashable b) => Graph UniqueLabel a b where
>>          ...
>>          buildGraph = ... some use of containers libraries that
>> require context ...
>>          ...
>>    lookupNode :: Hashable a => UniqueLabel a b -> a -> Node
>>    -- etc
>>
>>
>> Cheers,
>> Thomas
>>
>> P.S.  Please do educate me if I simply missed or misunderstood some
>> feature of FGL.
>
> Well, there *is* the NodeMap module, but I haven't really used it so
> I'm not sure if it does what you want.
>
> We did start upon a version of FGL which had these type variables in
> the class, but it got a little fiddly; the ability to have superclass
> constraints should solve this but I haven't touched FGL for a while,
> as I've been working on some other graph library code for planar
> graphs, with the plan to take my experience from writing this library
> into a "successor" to FGL.
>
> However, my experience with designing this planar graph library has
> led me to using abstract (i.e. non-exported constructor) ID types for
> nodes and edges and finding them rather useful, but then I'm more
> concerned about the _structure_ of the graph rather than the items
> stored within it.  As such, I'd appreciate you explaining to me
> (off-list is OK) why you want/need such a label -> node mapping so
> that I can try and work out a way to incorporate such functionality.
>
> --
> 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] FGL custom node identification (Label -> Node lookup)

2011-11-24 Thread Ivan Lazar Miljenovic
On 25 November 2011 05:13, Thomas DuBuisson  wrote:
> My thinking on this was that something akin to NodeMap should be
> _part_ of the graph structure.  This would be more convenient and
> allow the graph and nodemap operations to apply to a single data
> structure.
>
> Instead of:
>
>    insMapNode_ :: (Ord a, DynGraph g) => NodeMap a -> a -> g a b -> g a b
>
> You could have:
>
>    insMapNode_ :: (Ord a, DynGraph g) => a -> g a b -> g a b
>
> The only think stopping us from making a product data type like this
> is the inflexibility of the type classes, right?  Were we able to
> define (&) to update the nodemap too then we could keep these to
> structures in sync automatically instead of expecting the programmer
> to keep them paired correctly.

My thinking is to (eventually) make more fine-grained classes, and
have newtype wrappers that would add this kind of functionality (which
would even let you choose the type of constraint); i.e. adding a node
to a `(Hashable (NodeLabel g)) => HashableNodeMap g` would also add a
`NodeLabel g -> Node g` mapping to some internal lookup; is this what
you're after?

-- 
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