
I need help understanding how to express the following:
data (Cls a) => B a = B [a]
data GrB a b = GrB (B a)
instance Graph GrB where ...
In the methods for the instance specification, I need to perform Cls a operations on a. * As shown, the compiler complains that it cannot deduce (Cls a) from the context () on those methods. * I can't redefine the Graph methods to introduce the (Cls a) constraint [reasonable] * If I try to express the constraint as part of the Graph instance: "instance (Cls a) => Graph GrB where ..." then it says it's an ambiguous constraint because 'a' isn't mentioned. * I've tried specifying a functional constraint: "instance (Cls a) => Graph GrB | GrB -> a where ..." but that's not valid for an instance declaration. * I can't include a in the GrB instance: "instance (Cls a) => Graph (GrB a b) where ..." because that's a kind conflict. Suggestions/solutions are appreciated. Thanks! -- -KQ

"Kevin Quick"
I need help understanding how to express the following:
data (Cls a) => B a = B [a]
I think this only works if you have a forall in there.
data GrB a b = GrB (B a)
instance Graph GrB where ...
In the methods for the instance specification, I need to perform Cls a operations on a.
* As shown, the compiler complains that it cannot deduce (Cls a) from the context () on those methods.
You need to explicitly state them again (which is why putting the constraint in the data definition is pointless).
* I can't redefine the Graph methods to introduce the (Cls a) constraint [reasonable]
Not sure if you can.
* If I try to express the constraint as part of the Graph instance: "instance (Cls a) => Graph GrB where ..." then it says it's an ambiguous constraint because 'a' isn't mentioned.
Right, because the instance is on GrB _only_, not on the values it contains.
* I've tried specifying a functional constraint: "instance (Cls a) => Graph GrB | GrB -> a where ..." but that's not valid for an instance declaration. * I can't include a in the GrB instance: "instance (Cls a) => Graph (GrB a b) where ..." because that's a kind conflict.
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
That's solid advice in general, but it's still not going to work here if any of the functions needed for the instance of Graph require the type class constraint. The same problem comes up some times with the Monad class. For example, if you wanted to make a monad instance for Set a, you need "(Ord a) => " in the instance functions. I think associated types can work around this, if Graph used them for the a and b types, but I've never tried that so I don't actually know how it works. A solution to the monad problem I just mentioned is outlined here as 'restricted monads': http://okmij.org/ftp/Haskell/types.html#restricted-datatypes Perhaps you can try either associated types or the restricted monad approach? Unfortunately, I think both of them require you to change FGL instead of just your code, although maybe not with the restricted monad stuff. I don't recall how invasive that approach is. Jason

On Fri, Apr 30, 2010 at 11:30 PM, Jason Dagit
On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
That's solid advice in general, but it's still not going to work here if any of the functions needed for the instance of Graph require the type class constraint.
The same problem comes up some times with the Monad class. For example, if you wanted to make a monad instance for Set a, you need "(Ord a) => " in the instance functions.
I think associated types can work around this, if Graph used them for the a and b types, but I've never tried that so I don't actually know how it works.
A solution to the monad problem I just mentioned is outlined here as 'restricted monads': http://okmij.org/ftp/Haskell/types.html#restricted-datatypes
Looking over this real quick, I think the Graph class should be changed to mention a and b: class Graph (gr a b) where ... Then your instances would be able to mention constraints: instance Cls a => Graph (GrB a b) where ... Why wasn't the Graph class designed this way? My guess: It was probably a decision that predated multiparameter type classes. Jason

On May 1, 2010, at 02:38 , Jason Dagit wrote:
Why wasn't the Graph class designed this way? My guess: It was probably a decision that predated multiparameter type classes.
Or a specific decision was made to stick to Haskell'98 compatibility. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

"Brandon S. Allbery KF8NH"
On May 1, 2010, at 02:38 , Jason Dagit wrote:
Why wasn't the Graph class designed this way? My guess: It was probably a decision that predated multiparameter type classes.
Or a specific decision was made to stick to Haskell'98 compatibility.
I would also hazard a guess that it predates MPTCs (but don't know when that extension that came out so I can't be sure). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Sorry for the useless noise, I realised just after I sent this that
that is what Jason said initially :s
On 1 May 2010 17:02, Ivan Lazar Miljenovic
"Brandon S. Allbery KF8NH"
writes: On May 1, 2010, at 02:38 , Jason Dagit wrote:
Why wasn't the Graph class designed this way? My guess: It was probably a decision that predated multiparameter type classes.
Or a specific decision was made to stick to Haskell'98 compatibility.
I would also hazard a guess that it predates MPTCs (but don't know when that extension that came out so I can't be sure).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Jason Dagit
On Fri, Apr 30, 2010 at 11:30 PM, Jason Dagit
wrote: Looking over this real quick, I think the Graph class should be changed to mention a and b: class Graph (gr a b) where ...
Won't work: you need to specify that gr has kind * -> * -> *; this is exactly the same as how Functor, Monad, etc. are defined.
Then your instances would be able to mention constraints:
instance Cls a => Graph (GrB a b) where ...
Why wasn't the Graph class designed this way? My guess: It was probably a decision that predated multiparameter type classes.
That's not an MPTC (it would be more like "class Graph gr a b" if it was) and doesn't matter in this case anyway. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Jason Dagit
On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
That's solid advice in general, but it's still not going to work here if any of the functions needed for the instance of Graph require the type class constraint.
The Graph class doesn't care what the labels are, so it should matter about the constraint. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, Apr 30, 2010 at 11:53 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Jason Dagit
writes: On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
That's solid advice in general, but it's still not going to work here if any of the functions needed for the instance of Graph require the type class constraint.
The Graph class doesn't care what the labels are, so it should matter about the constraint.
Perhaps this "working" example illustrates the change I want to make. Working in the sense that it type checks but it's a silly example just to illustrate the point: \begin{code} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Graph where import Data.Graph.Inductive.Graph hiding (Graph) -- Defive some arbitrary class, and give it a 'boring' -- reason to use it. class Cls a where boring :: a data Blah = Blah -- Make sure we have at least one instance, but not really needed for this example instance Cls Blah where boring = Blah data B a = B [a] data GrB a b = GrB (B a) -- Just copy the bits from FGL that are interesting here class Graph gr a b where empty :: gr a b -- | True if the given 'Graph' is empty. isEmpty :: gr a b -> Bool -- | Create a 'Graph' from the list of 'LNode's and 'LEdge's. mkGraph :: [LNode a] -> [LEdge b] -> gr a b -- | A list of all 'LNode's in the 'Graph'. labNodes :: gr a b -> [LNode a] instance Cls a => Graph GrB a b where empty = GrB (B [boring]) isEmpty (GrB (B [])) = True isEmpty _ = False mkGraph _ _ = GrB (B []) labNodes _ = [] \end{code} The Graph class is actually unchanged other than mentioning 'a' and 'b'. This mention of 'a' and 'b' allows instance writers to add contexts other than () when defining instances. Jason

Hmmm.... this is an interesting way of doing it, but I would argue that
it's pointless: the fact that you're using MPTCs doesn't give you
anything extra that the original class. Furthermore, as I said earlier,
it doesn't make sense to constrain the label type just to make an
instance of a type class.
(Now, if we had other functions in there which _might_ depend on the
label types, this _would_ make sense; as it stands however, it doesn't.)
Jason Dagit
Perhaps this "working" example illustrates the change I want to make. Working in the sense that it type checks but it's a silly example just to illustrate the point:
\begin{code} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Graph where
import Data.Graph.Inductive.Graph hiding (Graph)
-- Defive some arbitrary class, and give it a 'boring' -- reason to use it. class Cls a where boring :: a
data Blah = Blah
-- Make sure we have at least one instance, but not really needed for this example instance Cls Blah where boring = Blah
data B a = B [a]
data GrB a b = GrB (B a)
-- Just copy the bits from FGL that are interesting here class Graph gr a b where empty :: gr a b -- | True if the given 'Graph' is empty. isEmpty :: gr a b -> Bool -- | Create a 'Graph' from the list of 'LNode's and 'LEdge's. mkGraph :: [LNode a] -> [LEdge b] -> gr a b -- | A list of all 'LNode's in the 'Graph'. labNodes :: gr a b -> [LNode a]
instance Cls a => Graph GrB a b where empty = GrB (B [boring]) isEmpty (GrB (B [])) = True isEmpty _ = False mkGraph _ _ = GrB (B []) labNodes _ = [] \end{code}
The Graph class is actually unchanged other than mentioning 'a' and 'b'. This mention of 'a' and 'b' allows instance writers to add contexts other than () when defining instances.
Jason
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sat, May 1, 2010 at 12:23 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Hmmm.... this is an interesting way of doing it, but I would argue that it's pointless: the fact that you're using MPTCs doesn't give you anything extra that the original class. Furthermore, as I said earlier, it doesn't make sense to constrain the label type just to make an instance of a type class.
(Now, if we had other functions in there which _might_ depend on the label types, this _would_ make sense; as it stands however, it doesn't.)
Try removing "Cls a" from the instance. You'll notice that my empty does depend on a having a Cls instance because it will fail to compile. In other words, I don't understand what you're talking about. I did need the constraint to define my instance. And if that example gets boring, try making an instance of Set for Monad. Then re-read the article I linked from Oleg's website. I'm not understanding your point, and I suspect you're not understanding mine :) Jason

Jason Dagit
On Sat, May 1, 2010 at 12:23 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Hmmm.... this is an interesting way of doing it, but I would argue that it's pointless: the fact that you're using MPTCs doesn't give you anything extra that the original class. Furthermore, as I said earlier, it doesn't make sense to constrain the label type just to make an instance of a type class.
(Now, if we had other functions in there which _might_ depend on the label types, this _would_ make sense; as it stands however, it doesn't.)
Try removing "Cls a" from the instance. You'll notice that my empty does depend on a having a Cls instance because it will fail to compile. In other words, I don't understand what you're talking about. I did need the constraint to define my instance.
Except that example is bogus: "isEmpty empty" returns False.
And if that example gets boring, try making an instance of Set for Monad.
My understanding was that Set couldn't be a Monad specifically why you can't make it one: Monads shouldn't constrain the value of the type contained within.
Then re-read the article I linked from Oleg's website. I'm not understanding your point, and I suspect you're not understanding mine :)
My point was that Kevin was doing it wrong and didn't need a constraint there; what's yours? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sat, May 1, 2010 at 12:49 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Jason Dagit
writes: On Sat, May 1, 2010 at 12:23 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
Hmmm.... this is an interesting way of doing it, but I would argue that it's pointless: the fact that you're using MPTCs doesn't give you anything extra that the original class. Furthermore, as I said earlier, it doesn't make sense to constrain the label type just to make an instance of a type class.
(Now, if we had other functions in there which _might_ depend on the label types, this _would_ make sense; as it stands however, it doesn't.)
Try removing "Cls a" from the instance. You'll notice that my empty does depend on a having a Cls instance because it will fail to compile. In other words, I don't understand what you're talking about. I did need the constraint to define my instance.
Except that example is bogus: "isEmpty empty" returns False.
I thought we were discussing how expressive the Graph typeclass is, not whether I made a sensible implementation. I mean, I could pretty easily fix that "problem", but I think that's not the important topic. For example, change empty to this: empty = GrB (B ([] `asTypeOf` [boring])) Without seeing all of Kevin's instance, it's really hard to say whether or not it actually matters for him. I'm not understanding how you can automatically infer it doesn't matter here.
And if that example gets boring, try making an instance of Set for Monad.
My understanding was that Set couldn't be a Monad specifically why you can't make it one: Monads shouldn't constrain the value of the type contained within.
I'm not a category theorist, but others seem to have looked into that issue in depth: http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros At the bottom, you'll see some extra monad laws that need to be satisfied due to the constraint. In particular: fmap f . return == return . f fmap f . join == join . fmap (fmap f)
Then re-read the article I linked from Oleg's website. I'm not understanding your point, and I suspect you're not understanding mine :)
My point was that Kevin was doing it wrong and didn't need a constraint there; what's yours?
I completely agreed that having the constraint in the data declaration was a bad idea. Then I took it a step further to assume it may still come up in the definition of the Graph instance for Kevin or others. So then I made up a silly example where it does matter. Hopefully Kevin will post back letting us know what worked (or didn't) for him. Jason

Jason Dagit
On Sat, May 1, 2010 at 12:49 AM, Ivan Lazar Miljenovic < I thought we were discussing how expressive the Graph typeclass is, not whether I made a sensible implementation. I mean, I could pretty easily fix that "problem", but I think that's not the important topic. For example, change empty to this: empty = GrB (B ([] `asTypeOf` [boring]))
But what is the point of that? That doesn't give you anything extra than specifying the type when you use it. Anyway, a better reason that I just thought of is that for some reason the type can only accept values of a certain type and thus mkGraph needs the constraint. However, I believe this goes against "the spirit" of the class (and would cause problem with nmap, emap, etc.). A better solution would be my still-so-far-mostly-vapourware generic graph class set where there is no requirement that the label types be mappable (which means I can't just scrap those classes when Louis and I start working on the new-and-improved FGL :s).
I'm not a category theorist, but others seem to have looked into that issue in depth: http://www.randomhacks.net/articles/2007/03/15/data-set-monad-haskell-macros
Hmmm... his code samples using the list monad seem to be non-existant for me, so I can't comment on them nor his rationales why this would be a good thing. Anyway, this split looks like the Applicative/etc. split that people have proposed. However, I still seem to recall someone telling me on #haskell that Monads, etc. are specifically _not_ meant to constrain the value type.
I completely agreed that having the constraint in the data declaration was a bad idea. Then I took it a step further to assume it may still come up in the definition of the Graph instance for Kevin or others. So then I made up a silly example where it does matter. Hopefully Kevin will post back letting us know what worked (or didn't) for him.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Furthermore, as I said earlier, it doesn't make sense to constrain the label type just to make an instance of a type class.
(Now, if we had other functions in there which _might_ depend on the label types, this _would_ make sense; as it stands however, it doesn't.)
You'll notice that my empty does depend on a having a Cls instance because it will fail to compile. [...] I'm not understanding your point, and I suspect you're not understanding mine :)
Let's assume he did understand your point. I think Ivan doubt's that there is any real need for the change because (while defining the set monad may make sense) "it does not make sense" to wish for being able to use additional constraints when defining the specific functions that are currently in the Graph class. I'm not sure if I agree. It would be interesting to see whether the real graph behind the original problem is an example where such additional constraints are really necessary and make sense. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

Sebastian Fischer
Furthermore, as I said earlier, it doesn't make sense to constrain the label type just to make an instance of a type class.
(Now, if we had other functions in there which _might_ depend on the label types, this _would_ make sense; as it stands however, it doesn't.)
You'll notice that my empty does depend on a having a Cls instance because it will fail to compile. [...] I'm not understanding your point, and I suspect you're not understanding mine :)
Let's assume he did understand your point. I think Ivan doubt's that there is any real need for the change because (while defining the set monad may make sense) "it does not make sense" to wish for being able to use additional constraints when defining the specific functions that are currently in the Graph class.
My objections were that there are no ways any such Graph instance would/should use any of the label values when defining definitions for the various methods; the labels are just meant to be extra things _attached_ to the nodes and edges.
I'm not sure if I agree. It would be interesting to see whether the real graph behind the original problem is an example where such additional constraints are really necessary and make sense.
Well, yes, having Kevin actually responding back would help ;-) -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, 30 Apr 2010 23:30:21 -0700, Jason Dagit
On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
I need to use Cls methods in the Graph methods: see below. More specifically, the Node decorators (type 'a') need to be of class Cls as well, but I can't figure out how to do this.
That's solid advice in general, but it's still not going to work here if any of the functions needed for the instance of Graph require the type class constraint.
Yes.
A solution to the monad problem I just mentioned is outlined here as 'restricted monads': http://okmij.org/ftp/Haskell/types.html#restricted-datatypes
I'll read this, but my brain has low Oleg-ability, so it may take me some time to begin to understand. Thanks for the reference though.
Perhaps you can try either associated types or the restricted monad approach? Unfortunately, I think both of them require you to change FGL instead of just your code, although maybe not with the restricted monad stuff. I don't recall how invasive that approach is.
Yes, I was hoping to use FGL directly (or it's replacement as I've scanned some of the recent Cafe discussions and seen that Ivan in particular is undertaking this). The key here is that the decorators for the Node are of type a, and I need that type a to be of (Cls a) because I use the methods in Cls a to implement the Graph functionality. I've attached a simple example below that attempts to demonstrate this need (and my numerous failures). {-# LANGUAGE RankNTypes #-} module Main where import Data.Graph.Inductive.Graph class Cls a where int :: a -> Int -- just to have something data (Cls a) => B a = B [a] -- The intent is that B is a collection of objects fulfilling the Cls -- class interface. It is also the intent to represent B as a Graph -- object. However, in order to create the Graph, the Cls operations -- are needed. -- To make a Graph representation of B, I need to convert my -- univariant B datatype into a bivariant type. This is odd because: -- (1) I ignore/drop b because it's not needed, and (2) I have a -- constraint on a imposed by B. data GrB a b = GrB (B a) -- data (Cls a) => GrB a b = GrB (B a) -- no difference in compilation errors instance Graph GrB where -- instance (Cls a) => Graph GrB where -- error: ambiguous constraint, must mention type a -- instance (Cls a) => forall a. Graph GrB where -- error: malformed instance header -- instance (Cls a) Graph GrB | GrB -> a where -- error: parse error on | -- empty :: (Cls a) => GrB a b -- error: Misplaced type signature (can't redefine the type) empty = GrB (B []) -- error: could not deduce (Cls a) from context () for B isEmpty (GrB (B l)) = null l match _ g = (Nothing, g) -- Actually need Cls methods on 'a' type to generate the non-trivial case mkGraph n e = GrB (B []) -- TBD labNodes g = [] -- TBD main = putStrLn "ok" Perhaps I need some alternative method here, or perhaps as has been suggested I'm trying to use something that's older/Haskell-98 specific that can't support this. Thanks again for the advice and help. Sorry I was rude in not answering for so long: shortly after my original post I realized sleep was needed. -- -KQ

"Kevin Quick"
Yes, I was hoping to use FGL directly (or it's replacement as I've scanned some of the recent Cafe discussions and seen that Ivan in particular is undertaking this).
FGL isn't really set up for this kind of "the data type _must_ be restricted" approach.
The key here is that the decorators for the Node are of type a, and I need that type a to be of (Cls a) because I use the methods in Cls a to implement the Graph functionality. I've attached a simple example below that attempts to demonstrate this need (and my numerous failures).
{-# LANGUAGE RankNTypes #-}
module Main where
import Data.Graph.Inductive.Graph
class Cls a where int :: a -> Int -- just to have something
data (Cls a) => B a = B [a]
-- The intent is that B is a collection of objects fulfilling the Cls -- class interface. It is also the intent to represent B as a Graph -- object. However, in order to create the Graph, the Cls operations -- are needed.
-- To make a Graph representation of B, I need to convert my -- univariant B datatype into a bivariant type. This is odd because: -- (1) I ignore/drop b because it's not needed, and (2) I have a -- constraint on a imposed by B.
data GrB a b = GrB (B a) -- data (Cls a) => GrB a b = GrB (B a) -- no difference in compilation errors
instance Graph GrB where -- instance (Cls a) => Graph GrB where -- error: ambiguous constraint, must mention type a -- instance (Cls a) => forall a. Graph GrB where -- error: malformed instance header -- instance (Cls a) Graph GrB | GrB -> a where -- error: parse error on | -- empty :: (Cls a) => GrB a b -- error: Misplaced type signature (can't redefine the type) empty = GrB (B []) -- error: could not deduce (Cls a) from context () for B
isEmpty (GrB (B l)) = null l
match _ g = (Nothing, g) -- Actually need Cls methods on 'a' type to generate the non-trivial case
mkGraph n e = GrB (B []) -- TBD labNodes g = [] -- TBD
Unless you have something else you haven't put here, I don't see any reason why you have to have the constraint on the datatype rather than on the actual functions (outside of the class instance) you need them for later on.
Thanks again for the advice and help. Sorry I was rude in not answering for so long: shortly after my original post I realized sleep was needed.
Yeah, that pesky sleep thing... -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sat, 01 May 2010 15:42:09 -0700, Ivan Lazar Miljenovic
instance Graph GrB where -- instance (Cls a) => Graph GrB where -- error: ambiguous constraint, must mention type a -- instance (Cls a) => forall a. Graph GrB where -- error: malformed instance header -- instance (Cls a) Graph GrB | GrB -> a where -- error: parse error on | -- empty :: (Cls a) => GrB a b -- error: Misplaced type signature (can't redefine the type) empty = GrB (B []) -- error: could not deduce (Cls a) from context () for B
isEmpty (GrB (B l)) = null l
match _ g = (Nothing, g) -- Actually need Cls methods on 'a' type to generate the non-trivial case
mkGraph n e = GrB (B []) -- TBD labNodes g = [] -- TBD
Unless you have something else you haven't put here, I don't see any reason why you have to have the constraint on the datatype rather than on the actual functions (outside of the class instance) you need them for later on.
I was trying to put them on the inside. Essentially I was trying to use the 'a' portion of the LNode as a type that would provide methods from which I could reconstruct the shape of the Graph. Or to put it another way, I had a collection of data and I wanted to be able to say "this container of data is also useable as a graph" by using class operations on the data. I've discovered an alternative, workable approach to the issue. After coming to terms that the instance of Graph could impose no restrictions on the node (or edge) labels and that they were (as you previously mentioned) simply "decorators" for the node, I determined that I could achieve my goal by writing a converter from "Cls" -> "a Graph instance for a" and I simply used Data.Graph.Inductive.Tree as the "a Graph instance" portion. import Data.Graph.Inductive.Tree clsToGraph :: (Cls a) => B a -> Gr a () clsToGraph b = mkGraph (nodes b) (edges b) where nodes x = ... edges x = ... The downside of this, to my procedurally-trained brain is that (1) I've now duplicated each 'a' in two different datastructures, and (2) I've had to pay--albeit lazily--for the conversion from B to the tree container represented by Gr. The nascent functionaly-trained portion of my brain would like to think that GHC (or other) is smart enough to not create duplicate copies... I'm not sure that's true though. I think I was probably fooling myself about (2) though: it was always there, just more explicitly now. It's one of the joys of Haskell: it saves your from your own stupid ideas. :-) -- -KQ

"Kevin Quick"
I was trying to put them on the inside. Essentially I was trying to use the 'a' portion of the LNode as a type that would provide methods from which I could reconstruct the shape of the Graph. Or to put it another way, I had a collection of data and I wanted to be able to say "this container of data is also useable as a graph" by using class operations on the data.
I've discovered an alternative, workable approach to the issue. After coming to terms that the instance of Graph could impose no restrictions on the node (or edge) labels and that they were (as you previously mentioned) simply "decorators" for the node, I determined that I could achieve my goal by writing a converter from "Cls" -> "a Graph instance for a" and I simply used Data.Graph.Inductive.Tree as the "a Graph instance" portion.
import Data.Graph.Inductive.Tree
clsToGraph :: (Cls a) => B a -> Gr a () clsToGraph b = mkGraph (nodes b) (edges b) where nodes x = ... edges x = ...
This is the more typical/idiomatic/proper way of doing it in Haskell; this means that each function is typically as specific in terms of constraints as it has to be and no more (which means it's easier to reuse, and we all like re-using functions!).
The downside of this, to my procedurally-trained brain is that (1) I've now duplicated each 'a' in two different datastructures, and (2) I've had to pay--albeit lazily--for the conversion from B to the tree container represented by Gr. The nascent functionaly-trained portion of my brain would like to think that GHC (or other) is smart enough to not create duplicate copies... I'm not sure that's true though. I think I was probably fooling myself about (2) though: it was always there, just more explicitly now.
Not sure how this is any more expensive than specifying that it can only have values of type a that match the constraint; more specifically you can have: clsToGraph :: (Cls a) => B a -> Gr (B a) () clsToGraph b = ... (this of course assumes this makes sense for your data types).
It's one of the joys of Haskell: it saves your from your own stupid ideas. :-)
Exactly; the type system is a straight jacket (in comparison to Python's, etc.), but a nice comfortable roomy straight jacket with plenty of give which lets you do most things but doesn't let you jump over 10 storey high railings into the traffic on the highway below (unless you pull out the magic unsafeRemoveStraighJacket function, in which case all bets are off). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On May 1, 2010, at 8:08 AM, Ivan Lazar Miljenovic wrote:
* I can't redefine the Graph methods to introduce the (Cls a) constraint [reasonable]
Not sure if you can.
I think Kevin means that he cannot change the signature of the methods in the Graph class because those are defined in the FGL package.
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
Those seem to be the methods of the Graph class, where he can't place the constraints. Kevin may have a version of makeGraph with additional constraints but cannot use it to to define a Graph instance. Sebastian -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On Sat, 01 May 2010 01:01:47 -0700, Sebastian Fischer
On May 1, 2010, at 8:08 AM, Ivan Lazar Miljenovic wrote:
* I can't redefine the Graph methods to introduce the (Cls a) constraint [reasonable]
Not sure if you can.
I think Kevin means that he cannot change the signature of the methods in the Graph class because those are defined in the FGL package.
Mostly. If I was able to redefine the method to add the class constraint in *my* code, that would be "what I wanted" but clearly wrong from the general type perspective: once defined it should not be possible to redefine. I was more trying to indicate that I'd been flailing around and trying everything, even things that make me look stupid. :-)
You're putting the constraint in the wrong places: put the "(Cls a) => " in the actual functions where you need it.
Those seem to be the methods of the Graph class, where he can't place the constraints. Kevin may have a version of makeGraph with additional constraints but cannot use it to to define a Graph instance.
Exactly. I posted a separate response with more details, but this is my problem. Actually, I'm even struggling defining the "empty" method of Graph. -- -KQ
participants (6)
-
Brandon S. Allbery KF8NH
-
Ivan Lazar Miljenovic
-
Ivan Miljenovic
-
Jason Dagit
-
Kevin Quick
-
Sebastian Fischer