
Hi, I want to make a function that returns a Foldable instance, briefly, something like this: import Data.Foldable test :: Foldable f => f Int test = [1,2,3,4] But I get this error: Couldn't match expected type `f' against inferred type `[]' `f' is a rigid type variable bound by the type signature for `test' at Test.hs:3:17 In the expression: [1, 2, 3, 4] In the definition of `test': test = [1, 2, 3, ....] How can I make a function like the one above? I'm creating different implementations of a multimap, using a Set and a [], and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable instance. Thanks!!! -- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On 5/3/11 21:31 , Federico Mastellone wrote:
I want to make a function that returns a Foldable instance, briefly, something like this:
import Data.Foldable
test :: Foldable f => f Int test = [1,2,3,4]
But I get this error:
Couldn't match expected type `f' against inferred type `[]' `f' is a rigid type variable bound by the type signature for `test' at Test.hs:3:17 In the expression: [1, 2, 3, 4] In the definition of `test': test = [1, 2, 3, ....]
Right; you're not returning a call-point-specified Foldable, you're returning a list always. I suspect you really want Traversable, not Foldable, so you can map elements from list to arbitrary Traversable; the reverse is then Data.Foldable.toList. (All Traversables are Foldables.) http://www.haskell.org/ghc/docs/latest/html/libraries/base-4.3.1.0/Data-Trav... - -- brandon s. allbery [linux,solaris,freebsd,perl] allbery.b@gmail.com system administrator [openafs,heimdal,too many hats] kf8nh -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.11 (Darwin) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/ iEYEARECAAYFAk3AvUkACgkQIn7hlCsL25UVCACcCVHdZL8u2JwD0WZ0P4V6+u3+ XcQAoLI/mqsekYCA2SmlyAfMNpn5Kjem =I0YQ -----END PGP SIGNATURE-----

On Tue, May 3, 2011 at 8:31 PM, Federico Mastellone
Hi,
I want to make a function that returns a Foldable instance, briefly, something like this:
import Data.Foldable
test :: Foldable f => f Int test = [1,2,3,4]
One point that helped me figure things out: The signature:
test :: Foldable f => f Int
does NOT mean "the value test satisfies the 'Foldable' contract' It means "the value test is of ANY 'Foldable' type". As in, it is of whatever type the caller picks, so long as it is 'Foldable'. And a list is not 'whatever type the caller picks.' Type classes are used in Haskell to write polymorphic functions, not for implementation hiding:
myNumericalCalculation :: Fractional n => n -> n -> Bool -> n
The caller can pick if they want to use limited precision Floats or Doubles, or if they want to pay the price for infinite precision Ratio types, or some type that I hadn't even thought of when I wrote the functions. Antoine
But I get this error:
Couldn't match expected type `f' against inferred type `[]' `f' is a rigid type variable bound by the type signature for `test' at Test.hs:3:17 In the expression: [1, 2, 3, 4] In the definition of `test': test = [1, 2, 3, ....]
How can I make a function like the one above?
I'm creating different implementations of a multimap, using a Set and a [], and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable instance.
Thanks!!!
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thank you both!
So, how can I return something that implements Foldable, so the caller
can fold without knowing if it is a [] or a Set and also be able to
change the underlying implementation without breaking the code?
With this I also want to avoid the extra overhead of the conversion to
or from lists, so the user will be folding the [] or Set directly,
depending on the implementation.
Creating an intermediate data type like this:
Temp a = TempList [a] | TempSet (Set a) | ...
That implements Foldable could be one solution, but is it a good one?
A cons of this is that every new implementation will have to alter
this type as well as creating the implementation.
Thanks again!
On Wed, May 4, 2011 at 12:27 AM, Antoine Latter
On Tue, May 3, 2011 at 8:31 PM, Federico Mastellone
wrote: Hi,
I want to make a function that returns a Foldable instance, briefly, something like this:
import Data.Foldable
test :: Foldable f => f Int test = [1,2,3,4]
One point that helped me figure things out:
The signature:
test :: Foldable f => f Int
does NOT mean "the value test satisfies the 'Foldable' contract'
It means "the value test is of ANY 'Foldable' type". As in, it is of whatever type the caller picks, so long as it is 'Foldable'. And a list is not 'whatever type the caller picks.'
Type classes are used in Haskell to write polymorphic functions, not for implementation hiding:
myNumericalCalculation :: Fractional n => n -> n -> Bool -> n
The caller can pick if they want to use limited precision Floats or Doubles, or if they want to pay the price for infinite precision Ratio types, or some type that I hadn't even thought of when I wrote the functions.
Antoine
But I get this error:
Couldn't match expected type `f' against inferred type `[]' `f' is a rigid type variable bound by the type signature for `test' at Test.hs:3:17 In the expression: [1, 2, 3, 4] In the definition of `test': test = [1, 2, 3, ....]
How can I make a function like the one above?
I'm creating different implementations of a multimap, using a Set and a [], and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable instance.
Thanks!!!
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On Tue, May 3, 2011 at 11:08 PM, Federico Mastellone
Thank you both!
So, how can I return something that implements Foldable, so the caller can fold without knowing if it is a [] or a Set and also be able to change the underlying implementation without breaking the code?
Well again, this is not what typeclasses are - in spite of the name, they are nothing like OO-style classes. If you want to hide your implementation, then (as you suggest bellow) you need to create a new type and not expose the details of the type. If you want the caller to be able to use the 'Foldable' family of functions then your new type needs to implement the 'Foldable' typeclass (or export equivalent functionality in some other way.)
With this I also want to avoid the extra overhead of the conversion to or from lists, so the user will be folding the [] or Set directly, depending on the implementation.
Creating an intermediate data type like this: Temp a = TempList [a] | TempSet (Set a) | ... That implements Foldable could be one solution, but is it a good one?
A cons of this is that every new implementation will have to alter this type as well as creating the implementation.
I really don't know enough about what you're trying to do to answer this - going with our current example the value:
test :: SomeType Int
only has one implementation. Feel free to respond back with more details about your problem. Antoine

Yes, I got confused between haskell type classes and OO classes.
I want to create different implementations of a multimap, for example
using lists and using Data.Set, and instead of providing functions
getValuesList and getValuesSet that return a [] and a Set respectively
I want to provide a more generic one, getValues that returns a
Foldable and avoid unnecessary conversions to and from lists. This way
the user folds directly the underlying structure, without having to
worry about which function is the best to fold the values. But I don't
know how to do this without an extra intermediate data type.
One implementation returns a list and the other a set, both Foldables.
But I can't make a function like the one below for this two
getValues :: Foldable f => MultiMap k v -> f v
On Wed, May 4, 2011 at 1:18 AM, Antoine Latter
On Tue, May 3, 2011 at 11:08 PM, Federico Mastellone
wrote: Thank you both!
So, how can I return something that implements Foldable, so the caller can fold without knowing if it is a [] or a Set and also be able to change the underlying implementation without breaking the code?
Well again, this is not what typeclasses are - in spite of the name, they are nothing like OO-style classes.
If you want to hide your implementation, then (as you suggest bellow) you need to create a new type and not expose the details of the type. If you want the caller to be able to use the 'Foldable' family of functions then your new type needs to implement the 'Foldable' typeclass (or export equivalent functionality in some other way.)
With this I also want to avoid the extra overhead of the conversion to or from lists, so the user will be folding the [] or Set directly, depending on the implementation.
Creating an intermediate data type like this: Temp a = TempList [a] | TempSet (Set a) | ... That implements Foldable could be one solution, but is it a good one?
A cons of this is that every new implementation will have to alter this type as well as creating the implementation.
I really don't know enough about what you're trying to do to answer this - going with our current example the value:
test :: SomeType Int
only has one implementation.
Feel free to respond back with more details about your problem.
Antoine
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On Wed, May 04, 2011 at 02:18:14AM -0300, Federico Mastellone wrote:
I want to create different implementations of a multimap, for example using lists and using Data.Set, and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable and avoid unnecessary conversions to and from lists. This way the user folds directly the underlying structure, without having to worry about which function is the best to fold the values. But I don't know how to do this without an extra intermediate data type.
A couple thoughts: First, I am not sure why you are so worried about avoiding an intermediate list. It smells like premature optimization to me. I doubt it will really make that big of a difference; and depending on how the result is used, the intermediate list might be optimized away anyway. Second, if you really want to *only* allow the caller of getValues to be able to fold the result, then you can just "inline" the fold, like so: getValues :: Monoid m => MultiMap k v -> (v -> m) -> m That is, instead of getting a Foldable thing and doing the fold themselves, they provide a mapping from values to some monoid and you do the fold for them. -Brent

On Wed, May 4, 2011 at 2:36 AM, Brent Yorgey
On Wed, May 04, 2011 at 02:18:14AM -0300, Federico Mastellone wrote:
I want to create different implementations of a multimap, for example using lists and using Data.Set, and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable and avoid unnecessary conversions to and from lists. This way the user folds directly the underlying structure, without having to worry about which function is the best to fold the values. But I don't know how to do this without an extra intermediate data type.
A couple thoughts:
First, I am not sure why you are so worried about avoiding an intermediate list. It smells like premature optimization to me. I doubt it will really make that big of a difference; and depending on how the result is used, the intermediate list might be optimized away anyway.
I want a function that returns the best way to traverse, fold, fmap, etc a part of the multimap without making any mention to the underlying structure. That would be instances of Functor, Foldable or Traversable.
Second, if you really want to *only* allow the caller of getValues to be able to fold the result, then you can just "inline" the fold, like so:
getValues :: Monoid m => MultiMap k v -> (v -> m) -> m
That is, instead of getting a Foldable thing and doing the fold themselves, they provide a mapping from values to some monoid and you do the fold for them.
Because the underlying structure is already Foldable, so why creating a dummy function for every method on the Foldable class that only calls the same function but in the underlying structure. I return a Foldable and the user can foldr1, foldl1, etc.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On 4 May 2011 07:25, Federico Mastellone
Because the underlying structure is already Foldable, so why creating a dummy function for every method on the Foldable class that only calls the same function but in the underlying structure.
If you make your MultiMap type and instance of Foldable, you get *every method on the Foldable class* for free anyway. Namely, you do not need to replicate functions with a Foldable constraint with your MultiMap data type. HTH, -- Ozgur Akgun

The MultiMap is based on Foldable types, but it's not Foldable (at
least there's no need to).
I made a mistake with the example function, the type I want is
getValues :: Foldable f => k -> MultiMap k v -> f v
but I don't know how to return a generic Foldable type.
On Wed, May 4, 2011 at 7:10 AM, Ozgur Akgun
On 4 May 2011 07:25, Federico Mastellone
wrote: Because the underlying structure is already Foldable, so why creating a dummy function for every method on the Foldable class that only calls the same function but in the underlying structure.
If you make your MultiMap type and instance of Foldable, you get every method on the Foldable class for free anyway. Namely, you do not need to replicate functions with a Foldable constraint with your MultiMap data type. HTH, -- Ozgur Akgun
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On Wed, May 4, 2011 at 7:18 AM, Federico Mastellone
Yes, I got confused between haskell type classes and OO classes.
I want to create different implementations of a multimap, for example using lists and using Data.Set, and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable and avoid unnecessary conversions to and from lists. This way the user folds directly the underlying structure, without having to worry about which function is the best to fold the values. But I don't know how to do this without an extra intermediate data type.
One implementation returns a list and the other a set, both Foldables. But I can't make a function like the one below for this two getValues :: Foldable f => MultiMap k v -> f v
Writing this function given your intention (doing different thing depending on the type) is equivalent to writing an instance of Foldable for your (MultiMap k). If the underlying structure of your multimaps is always foldable, it doesn't make sense to make a function like this, the multimaps themselves should be Foldable. This is not hard to do, refer to the doc ( http://www.haskell.org/ghc/docs/7.0-latest/html/libraries/base-4.3.1.0/Data-... ) to see how to write a minimal instance of Foldable. -- Jedaï

Sorry, the function type was incorrect, is for a part of the multimap,
not the entire multimap. But it's the same problem, a function that
returns a Foldable.
getValues :: Foldable f => k -> MultiMap k v -> f v
When the user asks for the values that a certain key contains I want
to return something that is generic and easy to play with while also
taking advantages of the underlying structure functions to avoid
repeated code.
On Wed, May 4, 2011 at 2:51 AM, Chaddaï Fouché
On Wed, May 4, 2011 at 7:18 AM, Federico Mastellone
wrote: Yes, I got confused between haskell type classes and OO classes.
I want to create different implementations of a multimap, for example using lists and using Data.Set, and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable and avoid unnecessary conversions to and from lists. This way the user folds directly the underlying structure, without having to worry about which function is the best to fold the values. But I don't know how to do this without an extra intermediate data type.
One implementation returns a list and the other a set, both Foldables. But I can't make a function like the one below for this two getValues :: Foldable f => MultiMap k v -> f v
Writing this function given your intention (doing different thing depending on the type) is equivalent to writing an instance of Foldable for your (MultiMap k). If the underlying structure of your multimaps is always foldable, it doesn't make sense to make a function like this, the multimaps themselves should be Foldable. This is not hard to do, refer to the doc ( http://www.haskell.org/ghc/docs/7.0-latest/html/libraries/base-4.3.1.0/Data-... ) to see how to write a minimal instance of Foldable.
-- Jedaï
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

I don't think anyone's pointed it out, but you can't build a Foldable structure with just Foldable. The Foldable class only allows you to "reduce" objects that already exist. For instance you cannot write this function where the Map is Data.Map rather than your MultiMap: getValues :: Foldable f => k -> Data.Map k v -> f v Really all you can do is produce an API like Data.Map, Data.Set have: toList :: MultiMap k v -> [(k,v)] toMap :: Ord k => MultiMap k v -> Map k v toSet :: (Ord k, Ord v) => MultiMap k v -> Set (k,v) In a nutshell, you seem to be wanting "container oblivious code". You can't really do this in Haskell I'm afraid. You can traverse and reduce containers generically with the Traverse and Foldable classes but you can't build them generically[*]. Best wishes Stephen [*] This might not be a disadvantage once you get over the initial disappointment - usually when you build something, you really do need to know what it is.

So, is it even possible to write a function with this type: getValues
:: Foldable f => k -> MultiMap k v -> f v ???
On Wed, May 4, 2011 at 7:46 AM, Stephen Tetley
I don't think anyone's pointed it out, but you can't build a Foldable structure with just Foldable.
The Foldable class only allows you to "reduce" objects that already exist.
For instance you cannot write this function where the Map is Data.Map rather than your MultiMap:
getValues :: Foldable f => k -> Data.Map k v -> f v
Really all you can do is produce an API like Data.Map, Data.Set have:
toList :: MultiMap k v -> [(k,v)] toMap :: Ord k => MultiMap k v -> Map k v toSet :: (Ord k, Ord v) => MultiMap k v -> Set (k,v)
In a nutshell, you seem to be wanting "container oblivious code". You can't really do this in Haskell I'm afraid. You can traverse and reduce containers generically with the Traverse and Foldable classes but you can't build them generically[*].
Best wishes
Stephen
[*] This might not be a disadvantage once you get over the initial disappointment - usually when you build something, you really do need to know what it is.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On 4 May 2011 13:21, Federico Mastellone
So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
I hadn't thought about it, but it's not possible to write that either. (!) You would need something like an Insertable class instead, plus Monoid so you can get an initial empty Set or List: getValues :: (Monoid (f v), Insertable f) => k -> MultiMap k v -> f v class Insertable f where insert :: a -> f a -> f a instance Insertable [] where insert a xs = (a:xs) -- Won't actually compile due to Ord constraint on Set -- (though there are ways with GHC to around that). -- instance Insert Set.Set where insert = Set.insert

On Wed, May 4, 2011 at 12:25 PM, Stephen Tetley
On 4 May 2011 13:21, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
I hadn't thought about it, but it's not possible to write that either. (!)
You would need something like an Insertable class instead, plus Monoid so you can get an initial empty Set or List:
getValues :: (Monoid (f v), Insertable f) => k -> MultiMap k v -> f v
But it won't be Foldable either, or is there a way to traverse a Monoid that I don't know?
class Insertable f where insert :: a -> f a -> f a
instance Insertable [] where insert a xs = (a:xs)
-- Won't actually compile due to Ord constraint on Set -- (though there are ways with GHC to around that). -- instance Insert Set.Set where insert = Set.insert
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On May 4, 2011 12:32 PM, "Federico Mastellone"
On Wed, May 4, 2011 at 12:25 PM, Stephen Tetley
wrote: On 4 May 2011 13:21, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
I hadn't thought about it, but it's not possible to write that either.
(!)
You would need something like an Insertable class instead, plus Monoid so you can get an initial empty Set or List:
getValues :: (Monoid (f v), Insertable f) => k -> MultiMap k v -> f v
But it won't be Foldable either, or is there a way to traverse a Monoid that I don't know?
With this signature the caller gets to pick the representation type; if they want something foldable they can choose it themselves.
class Insertable f where insert :: a -> f a -> f a
instance Insertable [] where insert a xs = (a:xs)
-- Won't actually compile due to Ord constraint on Set -- (though there are ways with GHC to around that). -- instance Insert Set.Set where insert = Set.insert
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wed, May 4, 2011 at 2:46 PM, Antoine Latter
On May 4, 2011 12:32 PM, "Federico Mastellone"
wrote: On Wed, May 4, 2011 at 12:25 PM, Stephen Tetley
wrote: On 4 May 2011 13:21, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
I hadn't thought about it, but it's not possible to write that either. (!)
You would need something like an Insertable class instead, plus Monoid so you can get an initial empty Set or List:
getValues :: (Monoid (f v), Insertable f) => k -> MultiMap k v -> f v
But it won't be Foldable either, or is there a way to traverse a Monoid that I don't know?
With this signature the caller gets to pick the representation type; if they want something foldable they can choose it themselves.
Now I understand, I just build the answer using mzero (from Monoid) and insert (From Insertable) and the calling context decides which representation is constructed. Thanks!
class Insertable f where insert :: a -> f a -> f a
instance Insertable [] where insert a xs = (a:xs)
-- Won't actually compile due to Ord constraint on Set -- (though there are ways with GHC to around that). -- instance Insert Set.Set where insert = Set.insert
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On Wed, May 4, 2011 at 2:21 PM, Federico Mastellone
So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
It isn't since there's nothing in the Foldable class that allows you to build one (only to consume one, do a fold over it, no "unfold"). But since this signature is _not_ the one you really want (it says you will deliver any Foldable your caller asks for), this isn't a problem, what you really want is :
data ExFoldable a = forall f . (Foldable f) => ExFoldable (f a)
instance Foldable ExFoldable where foldr f z (Exfoldable xs) = foldr f z xs
getValues :: k -> MultiMap k v -> Exfoldable v getValues k mm = ExFoldable (yourLookupFunction mm k)
or something like that. With this signature you're really saying you will deliver a Foldable without telling which one, like in OO. Now I'm not sure if this is such a good idea since as other have pointed, delivering a list is a pretty good and mostly simple option where the list itself is often optimized away. But if you really want it, Haskell can do it. (You'll need to activate some extensions to allow this) -- Jedaï

On Wed, May 4, 2011 at 1:22 PM, Chaddaï Fouché
On Wed, May 4, 2011 at 2:21 PM, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
It isn't since there's nothing in the Foldable class that allows you to build one (only to consume one, do a fold over it, no "unfold").
As it's impossible to build a function like this one below: getValues :: Foldable f => k -> MultiMap k v -> f v I know that it may be too difficult, but wouldn't be great to make this type illegal in Haskell ? You can't make a function that returns a class that has no method that builds an instance of that class unless another parameter of the function is of that class or allows you to build one instance of that class.
But since this signature is _not_ the one you really want (it says you will deliver any Foldable your caller asks for), this isn't a problem, what you really want is :
data ExFoldable a = forall f . (Foldable f) => ExFoldable (f a)
This will do the trick and it is better than maintaining an intermediate structure as I previously said. Thank you and Alexander for this tip.
instance Foldable ExFoldable where foldr f z (Exfoldable xs) = foldr f z xs
getValues :: k -> MultiMap k v -> Exfoldable v getValues k mm = ExFoldable (yourLookupFunction mm k)
or something like that. With this signature you're really saying you will deliver a Foldable without telling which one, like in OO.
Now I'm not sure if this is such a good idea since as other have pointed, delivering a list is a pretty good and mostly simple option where the list itself is often optimized away. But if you really want it, Haskell can do it.
(You'll need to activate some extensions to allow this)
-- Jedaï
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On Wed, May 4, 2011 at 1:08 PM, Federico Mastellone
On Wed, May 4, 2011 at 1:22 PM, Chaddaï Fouché
wrote: On Wed, May 4, 2011 at 2:21 PM, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
It isn't since there's nothing in the Foldable class that allows you to build one (only to consume one, do a fold over it, no "unfold").
As it's impossible to build a function like this one below: getValues :: Foldable f => k -> MultiMap k v -> f v I know that it may be too difficult, but wouldn't be great to make this type illegal in Haskell ? You can't make a function that returns a class that has no method that builds an instance of that class unless another parameter of the function is of that class or allows you to build one instance of that class.
But since this signature is _not_ the one you really want (it says you will deliver any Foldable your caller asks for), this isn't a problem, what you really want is :
data ExFoldable a = forall f . (Foldable f) => ExFoldable (f a)
This will do the trick and it is better than maintaining an intermediate structure as I previously said. Thank you and Alexander for this tip.
I really think that this is just a more complicated version of making your own wrapper type as discussed above. Both types:
data ExFoldable a = ...
and
newtype ResultType a = Result [a] deriving (Foldable)
offer up the exact same API to the caller. The second one is just easier to understand and requires fewer advanced language extensions. And if your goal is optimization, the 'ExFoldable' version is likely to be slower for the caller to fold over than if you had converted the result to a list and returned it, because with the 'ExFoldable' return type the compiler has less information to work with at the call site. Keep in mind I haven't benchmarked any of this :-) Antoine

On May 4, 2011, at 2:22 PM, Antoine Latter wrote:
On Wed, May 4, 2011 at 1:08 PM, Federico Mastellone
wrote: On Wed, May 4, 2011 at 1:22 PM, Chaddaï Fouché
wrote: On Wed, May 4, 2011 at 2:21 PM, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
It isn't since there's nothing in the Foldable class that allows you to build one (only to consume one, do a fold over it, no "unfold").
As it's impossible to build a function like this one below: getValues :: Foldable f => k -> MultiMap k v -> f v I know that it may be too difficult, but wouldn't be great to make this type illegal in Haskell ? You can't make a function that returns a class that has no method that builds an instance of that class unless another parameter of the function is of that class or allows you to build one instance of that class.
But since this signature is _not_ the one you really want (it says you will deliver any Foldable your caller asks for), this isn't a problem, what you really want is :
data ExFoldable a = forall f . (Foldable f) => ExFoldable (f a)
This will do the trick and it is better than maintaining an intermediate structure as I previously said. Thank you and Alexander for this tip.
I really think that this is just a more complicated version of making your own wrapper type as discussed above.
Both types:
data ExFoldable a = ...
and
newtype ResultType a = Result [a] deriving (Foldable)
offer up the exact same API to the caller. The second one is just easier to understand and requires fewer advanced language extensions.
And if your goal is optimization, the 'ExFoldable' version is likely to be slower for the caller to fold over than if you had converted the result to a list and returned it, because with the 'ExFoldable' return type the compiler has less information to work with at the call site. Keep in mind I haven't benchmarked any of this :-)
If you're really dead-set on eliminating lists, I'd suggest that your 'ResultType' just be a structure that contains a reference to a MultiMap and a key, or whatever other information you need to be able to implement foldMap. For example:
data FoldableView k v = FoldableView k (MultiMap k v) instance Foldable (FoldableView k) where {- ... -}
getValues :: k -> MultiMap k v -> FoldableView k v getValues k m = FoldableView k m
Then your users really can just fold over (a very lightweight view of) the MultiMap itself, with no intermediate structures of any kind. -- James

I still have a question about this. If you look at the Text.Regex.Posix library you can do this:
"asdf" =~ "asdf" :: String "asdf"
"asdf" =~ "asdf" :: Int 1 :t "asdf" =~ "asdf" "asdf" =~ "asdf" :: (RegexContext Regex [Char] target) => target
So, there is something similar to what the op was asking for. Why is
this possible, but his is not?
(sorry james meant to reply to all)
On Wed, May 4, 2011 at 2:51 PM, James Cook
On May 4, 2011, at 2:22 PM, Antoine Latter wrote:
On Wed, May 4, 2011 at 1:08 PM, Federico Mastellone
wrote: On Wed, May 4, 2011 at 1:22 PM, Chaddaï Fouché
wrote: On Wed, May 4, 2011 at 2:21 PM, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
It isn't since there's nothing in the Foldable class that allows you to build one (only to consume one, do a fold over it, no "unfold").
As it's impossible to build a function like this one below: getValues :: Foldable f => k -> MultiMap k v -> f v I know that it may be too difficult, but wouldn't be great to make this type illegal in Haskell ? You can't make a function that returns a class that has no method that builds an instance of that class unless another parameter of the function is of that class or allows you to build one instance of that class.
But since this signature is _not_ the one you really want (it says you will deliver any Foldable your caller asks for), this isn't a problem, what you really want is :
data ExFoldable a = forall f . (Foldable f) => ExFoldable (f a)
This will do the trick and it is better than maintaining an intermediate structure as I previously said. Thank you and Alexander for this tip.
I really think that this is just a more complicated version of making your own wrapper type as discussed above.
Both types:
data ExFoldable a = ...
and
newtype ResultType a = Result [a] deriving (Foldable)
offer up the exact same API to the caller. The second one is just easier to understand and requires fewer advanced language extensions.
And if your goal is optimization, the 'ExFoldable' version is likely to be slower for the caller to fold over than if you had converted the result to a list and returned it, because with the 'ExFoldable' return type the compiler has less information to work with at the call site. Keep in mind I haven't benchmarked any of this :-)
If you're really dead-set on eliminating lists, I'd suggest that your 'ResultType' just be a structure that contains a reference to a MultiMap and a key, or whatever other information you need to be able to implement foldMap. For example:
data FoldableView k v = FoldableView k (MultiMap k v) instance Foldable (FoldableView k) where {- ... -}
getValues :: k -> MultiMap k v -> FoldableView k v getValues k m = FoldableView k m
Then your users really can just fold over (a very lightweight view of) the MultiMap itself, with no intermediate structures of any kind.
-- James _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On May 4, 2011, at 3:26 PM, David McBride wrote:
I still have a question about this. If you look at the Text.Regex.Posix library you can do this:
"asdf" =~ "asdf" :: String "asdf"
"asdf" =~ "asdf" :: Int 1 :t "asdf" =~ "asdf" "asdf" =~ "asdf" :: (RegexContext Regex [Char] target) => target
So, there is something similar to what the op was asking for. Why is this possible, but his is not?
Because unlike the Foldable class, the RegexContext class does provide functions that return values of its type parameters. RegexContext is defined as follows:
class RegexLike regex source => RegexContext regex source target where match :: regex -> source -> target matchM :: Monad m => regex -> source -> m target
The 'match' function returns a value of type 'target'. For Foldable, though:
class Foldable t where fold :: Monoid m => t m -> m foldMap :: Monoid m => (a -> m) -> t a -> m foldr :: (a -> b -> b) -> b -> t a -> b foldl :: (a -> b -> a) -> a -> t b -> a foldr1 :: (a -> a -> a) -> t a -> a foldl1 :: (a -> a -> a) -> t a -> a
None of those functions return anything that mentions "t", so the Foldable class is not able to construct values of an unknown Foldable type. For a simpler example, the same ideas applies to more-familiar typeclasses defined in the Prelude. For example, you can have expressions of type "Num a => a", because the Num class defines a function "fromInteger :: Integer -> a" - so if you have an Integer, you can make a value of any type that is an instance of Num. But you cannot have a useful expression of type "Show a => a", because Show doesn't define any functions that produce values. -- James

Thanks James and Antoine, making a new type like ResultType or
FoldableView seems to be an elegant solution!
On Wed, May 4, 2011 at 3:51 PM, James Cook
On May 4, 2011, at 2:22 PM, Antoine Latter wrote:
On Wed, May 4, 2011 at 1:08 PM, Federico Mastellone
wrote: On Wed, May 4, 2011 at 1:22 PM, Chaddaï Fouché
wrote: On Wed, May 4, 2011 at 2:21 PM, Federico Mastellone
wrote: So, is it even possible to write a function with this type: getValues :: Foldable f => k -> MultiMap k v -> f v ???
It isn't since there's nothing in the Foldable class that allows you to build one (only to consume one, do a fold over it, no "unfold").
As it's impossible to build a function like this one below: getValues :: Foldable f => k -> MultiMap k v -> f v I know that it may be too difficult, but wouldn't be great to make this type illegal in Haskell ? You can't make a function that returns a class that has no method that builds an instance of that class unless another parameter of the function is of that class or allows you to build one instance of that class.
But since this signature is _not_ the one you really want (it says you will deliver any Foldable your caller asks for), this isn't a problem, what you really want is :
data ExFoldable a = forall f . (Foldable f) => ExFoldable (f a)
This will do the trick and it is better than maintaining an intermediate structure as I previously said. Thank you and Alexander for this tip.
I really think that this is just a more complicated version of making your own wrapper type as discussed above.
Both types:
data ExFoldable a = ...
and
newtype ResultType a = Result [a] deriving (Foldable)
offer up the exact same API to the caller. The second one is just easier to understand and requires fewer advanced language extensions.
And if your goal is optimization, the 'ExFoldable' version is likely to be slower for the caller to fold over than if you had converted the result to a list and returned it, because with the 'ExFoldable' return type the compiler has less information to work with at the call site. Keep in mind I haven't benchmarked any of this :-)
If you're really dead-set on eliminating lists, I'd suggest that your 'ResultType' just be a structure that contains a reference to a MultiMap and a key, or whatever other information you need to be able to implement foldMap. For example:
data FoldableView k v = FoldableView k (MultiMap k v) instance Foldable (FoldableView k) where {- ... -}
getValues :: k -> MultiMap k v -> FoldableView k v getValues k m = FoldableView k m
Then your users really can just fold over (a very lightweight view of) the MultiMap itself, with no intermediate structures of any kind.
-- James
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.

On Wed, May 4, 2011 at 2:51 AM, Chaddaï Fouché
Writing this function given your intention (doing different thing depending on the type) is equivalent to writing an instance of Foldable for your (MultiMap k). If the underlying structure of your multimaps is always foldable, it doesn't make sense to make a function like this, the multimaps themselves should be Foldable. This is not hard to do, refer to the doc ( http://www.haskell.org/ghc/docs/7.0-latest/html/libraries/base-4.3.1.0/Data-... ) to see how to write a minimal instance of Foldable.
I second this. I don't see how an instance of Foldable (MultiMap k) is different of what the OP wants. Much easier and nicer. Cheers, -- Felipe.

This probably isn't a good solution to your problem, but you could use
an existential type to hide what the type actually was. You need a GHC
extension (ExistentialQuantification, I think) for this to work. The
following code is completely untested and the syntax might be wrong,
but the idea should be right:
data SomethingFoldable = SomethingFoldable (forall f. Foldable f => f)
Now your function can return a value of type SomethingFoldable. Notice
that the type of SomethingFoldable is not parameterized by the type of
f: the "forall" keyword inside the parentheses means that the value
could be *any* type that satisfies the Foldable constraint.
Note that this hugely limits what the caller can do with the value.
They don't know what type the value is, so they can't use list
functions (because the value might be a Set or something else
Foldable) or Set functions (because the value might be a list or
something else Foldable). All they know is that the value is a member
of the Foldable class, so the only way the value can be used is in a
function that takes an arbitrary member of the Foldable class as a
value. (function :: Foldable f => ... -> f -> ...)
Because of this, I've found that this technique's usefulness is
limited to situations where you really want to be leveraging the type
system to do something interesting. In other cases, there is probably
just one function (since type classes generally don't have a lot of
member functions) that your caller would be applying to the returned
value, and you could just call that function within your function and
return the result of that. (You might have to add additional arguments
to your function, like a function to fold with or an initial value,
etc.)
Hope that helps you a bit.
Alex
On 3 May 2011 21:08, Federico Mastellone
Thank you both!
So, how can I return something that implements Foldable, so the caller can fold without knowing if it is a [] or a Set and also be able to change the underlying implementation without breaking the code?
With this I also want to avoid the extra overhead of the conversion to or from lists, so the user will be folding the [] or Set directly, depending on the implementation.
Creating an intermediate data type like this: Temp a = TempList [a] | TempSet (Set a) | ... That implements Foldable could be one solution, but is it a good one? A cons of this is that every new implementation will have to alter this type as well as creating the implementation.
Thanks again!
On Wed, May 4, 2011 at 12:27 AM, Antoine Latter
wrote: On Tue, May 3, 2011 at 8:31 PM, Federico Mastellone
wrote: Hi,
I want to make a function that returns a Foldable instance, briefly, something like this:
import Data.Foldable
test :: Foldable f => f Int test = [1,2,3,4]
One point that helped me figure things out:
The signature:
test :: Foldable f => f Int
does NOT mean "the value test satisfies the 'Foldable' contract'
It means "the value test is of ANY 'Foldable' type". As in, it is of whatever type the caller picks, so long as it is 'Foldable'. And a list is not 'whatever type the caller picks.'
Type classes are used in Haskell to write polymorphic functions, not for implementation hiding:
myNumericalCalculation :: Fractional n => n -> n -> Bool -> n
The caller can pick if they want to use limited precision Floats or Doubles, or if they want to pay the price for infinite precision Ratio types, or some type that I hadn't even thought of when I wrote the functions.
Antoine
But I get this error:
Couldn't match expected type `f' against inferred type `[]' `f' is a rigid type variable bound by the type signature for `test' at Test.hs:3:17 In the expression: [1, 2, 3, 4] In the definition of `test': test = [1, 2, 3, ....]
How can I make a function like the one above?
I'm creating different implementations of a multimap, using a Set and a [], and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable instance.
Thanks!!!
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thanks for the tip about ExistentialQuantification! I'll take a look at it.
On Wed, May 4, 2011 at 2:06 AM, Alexander Dunlap
This probably isn't a good solution to your problem, but you could use an existential type to hide what the type actually was. You need a GHC extension (ExistentialQuantification, I think) for this to work. The following code is completely untested and the syntax might be wrong, but the idea should be right:
data SomethingFoldable = SomethingFoldable (forall f. Foldable f => f)
Now your function can return a value of type SomethingFoldable. Notice that the type of SomethingFoldable is not parameterized by the type of f: the "forall" keyword inside the parentheses means that the value could be *any* type that satisfies the Foldable constraint.
Note that this hugely limits what the caller can do with the value. They don't know what type the value is, so they can't use list functions (because the value might be a Set or something else Foldable) or Set functions (because the value might be a list or something else Foldable). All they know is that the value is a member of the Foldable class, so the only way the value can be used is in a function that takes an arbitrary member of the Foldable class as a value. (function :: Foldable f => ... -> f -> ...)
Because of this, I've found that this technique's usefulness is limited to situations where you really want to be leveraging the type system to do something interesting. In other cases, there is probably just one function (since type classes generally don't have a lot of member functions) that your caller would be applying to the returned value, and you could just call that function within your function and return the result of that. (You might have to add additional arguments to your function, like a function to fold with or an initial value, etc.)
Hope that helps you a bit.
Alex
On 3 May 2011 21:08, Federico Mastellone
wrote: Thank you both!
So, how can I return something that implements Foldable, so the caller can fold without knowing if it is a [] or a Set and also be able to change the underlying implementation without breaking the code?
With this I also want to avoid the extra overhead of the conversion to or from lists, so the user will be folding the [] or Set directly, depending on the implementation.
Creating an intermediate data type like this: Temp a = TempList [a] | TempSet (Set a) | ... That implements Foldable could be one solution, but is it a good one? A cons of this is that every new implementation will have to alter this type as well as creating the implementation.
Thanks again!
On Wed, May 4, 2011 at 12:27 AM, Antoine Latter
wrote: On Tue, May 3, 2011 at 8:31 PM, Federico Mastellone
wrote: Hi,
I want to make a function that returns a Foldable instance, briefly, something like this:
import Data.Foldable
test :: Foldable f => f Int test = [1,2,3,4]
One point that helped me figure things out:
The signature:
test :: Foldable f => f Int
does NOT mean "the value test satisfies the 'Foldable' contract'
It means "the value test is of ANY 'Foldable' type". As in, it is of whatever type the caller picks, so long as it is 'Foldable'. And a list is not 'whatever type the caller picks.'
Type classes are used in Haskell to write polymorphic functions, not for implementation hiding:
myNumericalCalculation :: Fractional n => n -> n -> Bool -> n
The caller can pick if they want to use limited precision Floats or Doubles, or if they want to pay the price for infinite precision Ratio types, or some type that I hadn't even thought of when I wrote the functions.
Antoine
But I get this error:
Couldn't match expected type `f' against inferred type `[]' `f' is a rigid type variable bound by the type signature for `test' at Test.hs:3:17 In the expression: [1, 2, 3, 4] In the definition of `test': test = [1, 2, 3, ....]
How can I make a function like the one above?
I'm creating different implementations of a multimap, using a Set and a [], and instead of providing functions getValuesList and getValuesSet that return a [] and a Set respectively I want to provide a more generic one, getValues that returns a Foldable instance.
Thanks!!!
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult."
Tony Hoare, 1980 ACM Turing Award Lecture.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Federico Mastellone Computer Science Engineer - ITBA ".. there are two ways of constructing a software design: One way is to make it so simple that there are obviously no deficiencies, and the other way is to make it so complicated that there are no obvious deficiencies. The first method is far more difficult." Tony Hoare, 1980 ACM Turing Award Lecture.
participants (11)
-
Alexander Dunlap
-
Antoine Latter
-
Brandon S Allbery KF8NH
-
Brent Yorgey
-
Chaddaï Fouché
-
David McBride
-
Federico Mastellone
-
Felipe Almeida Lessa
-
James Cook
-
Ozgur Akgun
-
Stephen Tetley