
Hello, is there a way to defined something as a map to use in tuples? I tried this: mapTuple f (a, b) = (f a, f b) But the type inferred to it is not as generic as I wanted: mapTuple :: (t -> t1) -> (t, t) -> (t1, t1) Then I tried a different, but not much, implementation: mapTuple' f g (a, b) = (f a, g b) mapTuple f = mapTuple' f f But the inferred type was the same. Is there a way to define a function in which I can be able to do something as this? mapTuple show ("string", True) -- malebria Marco Túlio Gontijo e Silva Correio (MSN): malebria@riseup.net Jabber (GTalk): malebria@jabber.org Telefone: 33346720 Celular: 98116720 Endereço: Rua Paula Cândido, 257/201 Gutierrez 30430-260 Belo Horizonte/MG Brasil

2007/1/11, Marco Túlio Gontijo e Silva
Hello,
is there a way to defined something as a map to use in tuples? I tried this:
mapTuple f (a, b) = (f a, f b)
But the type inferred to it is not as generic as I wanted:
mapTuple :: (t -> t1) -> (t, t) -> (t1, t1)
Then I tried a different, but not much, implementation:
mapTuple' f g (a, b) = (f a, g b) mapTuple f = mapTuple' f f
But the inferred type was the same.
Is there a way to define a function in which I can be able to do something as this?
mapTuple show ("string", True)
Hi, you might want invistigate "heterogeneous lists" : in your case, it's "heterogeneous typle". There's a page lying on the wiki I think... It involves typeclasses and type quantifiers. Ciao, minh thu

Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
you might want invistigate "heterogeneous lists" : in your case, it's "heterogeneous typle".
But aren't tuples always heterogeneous? Regards. -- malebria Marco Túlio Gontijo e Silva Correio (MSN): malebria@riseup.net Jabber (GTalk): malebria@jabber.org Telefone: 33346720 Celular: 98116720 Endereço: Rua Paula Cândido, 257/201 Gutierrez 30430-260 Belo Horizonte/MG Brasil

2007/1/11, Marco Túlio Gontijo e Silva
Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
you might want invistigate "heterogeneous lists" : in your case, it's "heterogeneous typle".
But aren't tuples always heterogeneous?
You're right but the fact you apply a function on both element of the tuple constrains them to have the same type. Thus the problem is reminiscent of heterogeneous lists: how can you make (i.e. wrap) two values of different type so they have (after being wrapped) the same type ? I couldnt find the page I was refering but found this one: http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types Look at the part on heterogeneous list, the examples are the thing you want (but for a list, not for a tuple). Oh two things: 1/ I'm a bad haskell programmers since I have not enough experience (so maybe I'm throwing you in the bad direction but I prefer to answer so you not have to wait to long...); 2/ It's a bit of a habit here to answer with quite involved material even when a noob asks something (which I don't know if you are or not). Thus maybe the real answer to your question is wether what you ask for is really the root of the problem (I can't answer for you). Another way to do what you want if you just want to use the 'show' function above on some types (and not every instance of Show) is to wrap each type individually in a variant type something like this: data MyShowable = S String | B Bool myShow :: MyShowable -> String Optionnaly you can then make MyShowable an instance of Show. This way is much more 'basic level' haskell than the wiki page above. Cheers, mt

Em Qui, 2007-01-11 às 16:51 +0100, minh thu escreveu:
2007/1/11, Marco Túlio Gontijo e Silva
: Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
you might want invistigate "heterogeneous lists" : in your case, it's "heterogeneous typle".
But aren't tuples always heterogeneous?
You're right but the fact you apply a function on both element of the tuple constrains them to have the same type. Thus the problem is reminiscent of heterogeneous lists: how can you make (i.e. wrap) two values of different type so they have (after being wrapped) the same type ?
I couldnt find the page I was refering but found this one: http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types Look at the part on heterogeneous list, the examples are the thing you want (but for a list, not for a tuple).
Oh two things: 1/ I'm a bad haskell programmers since I have not enough experience (so maybe I'm throwing you in the bad direction but I prefer to answer so you not have to wait to long...); 2/ It's a bit of a habit here to answer with quite involved material even when a noob asks something (which I don't know if you are or not). Thus maybe the real answer to your question is wether what you ask for is really the root of the problem (I can't answer for you).
Another way to do what you want if you just want to use the 'show' function above on some types (and not every instance of Show) is to wrap each type individually in a variant type something like this: data MyShowable = S String | B Bool myShow :: MyShowable -> String
Optionnaly you can then make MyShowable an instance of Show. This way is much more 'basic level' haskell than the wiki page above.
Thanks for your answers. I found the page of heterogeneous collections in haskell wiki: http://haskell.org/haskellwiki/Heterogenous_collections But my point was trying to do this without having to convert it to a homogeneous tuple by using Dynamic. I read a little of the wiki page, and it gave me some ideas: (with ghci -fglasgow-exts) let mapTuple :: forall c d e f. (forall a b. a -> b) -> (c, d) -> (e, f); mapTuple f (x, y) = (f x, f y) works fine, but when I run: Prelude> mapTuple show ("string", True) <interactive>:1:9: Couldn't match expected type `b' (a rigid variable) against inferred type `String' `b' is bound by the polymorphic type `forall a b. a -> b' at <interactive>:1:0-29 In the first argument of `mapTuple', namely `show' In the expression: mapTuple show ("string", True) In the definition of `it': it = mapTuple show ("string", True) Prelude> And: Prelude> mapTuple head (["string"], [True]) <interactive>:1:9: Couldn't match expected type `a' (a rigid variable) against inferred type `[a1]' `a' is bound by the polymorphic type `forall a b. a -> b' at <interactive>:1:0-33 Expected type: a -> b Inferred type: [a1] -> a1 In the first argument of `mapTuple', namely `head' In the expression: mapTuple head (["string"], [True]) Prelude> This seemed to "work": Prelude> mapTuple (const undefined) ("string", True) (*** Exception: Prelude.undefined Prelude> The problem is it only works with forall a b. a -> b functions. I tried with exits, but I got an error: Prelude> let mapTuple :: forall c d e f. (exists a b. a -> b) -> (c, d) -> (e, f); mapTuple f (x, y) = (f x, f y) <interactive>:1:43: parse error on input `.' Prelude> Thanks for any help. -- malebria Marco Túlio Gontijo e Silva Correio (MSN): malebria@riseup.net Jabber (GTalk): malebria@jabber.org Telefone: 33346720 Celular: 98116720 Endereço: Rua Paula Cândido, 257/201 Gutierrez 30430-260 Belo Horizonte/MG Brasil

On 11-jan-2007, at 16:30, Marco Túlio Gontijo e Silva wrote:
Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
you might want invistigate "heterogeneous lists" : in your case, it's "heterogeneous typle".
But aren't tuples always heterogeneous?
Yes, and precisely therein lies the problem. There is no way for the compiler to infer that in tupleMap f (a, b) = (f a, f b) the type of f should be polymorphic. If you want it to be, explicitly require it to be so: tupleMap :: (forall a b . a -> b) -> (b,c) -> (d,e) tupleMap f (a,b) = (f a, f b) However, this will still not allow you to write tupleMap show ("string",3) as you require f to be fully polymorphic, and not constrained by any context. With regards, Arthur. -- /\ / | arthurvl@cs.uu.nl | Work like you don't need the money /__\ / | A friend is someone with whom | Love like you have never been hurt / \/__ | you can dare to be yourself | Dance like there's nobody watching

On 11/01/07, Marco Túlio Gontijo e Silva
is there a way to defined something as a map to use in tuples? I tried this:
mapTuple f (a, b) = (f a, f b)
But the type inferred to it is not as generic as I wanted:
mapTuple :: (t -> t1) -> (t, t) -> (t1, t1)
Let's think about what type we might want to give this. Here's a first attempt: mapTuple :: (a -> c) -> (a, b) -> (c, d) mapTuple f (x, y) = (f x, f y) But this won't typecheck, because we can only apply the function to the first element in the tuple from the type that we have. In other words, we don't know that we can pass values of type b into f. We could say: mapTuple :: (a -> c) -> (a, a) -> (c, c) But this isn't as polymorphic as you'd like. An alternative is sum types: mapTuple :: (Either a b -> c) -> (a, b) -> (c, c) mapTuple f (x, y) = (f $ Left x, f $ Right y) Note that we can't do: mapTuple :: (Either a b -> Either c d) -> (a, b) -> (c, d) Because we don't know that feeding a value of type c into f will yield a value of type d; f (Left x) might return a Right-tagged value. We could perhaps do this: mapTuple :: (Either a b -> (c, d)) -> (a, b) -> (c, d) mapTuple f (x, y) = (fst $ f $ Left x, snd $ f $ Right y) And a function would then return both a value of type c and d (possibly one of them being undefined). However, it doesn't really seem satisfactory to impose this constraint on our arguments. Instead, it seems we want to supply two functions: mapTuple :: (a -> b) -> (c - >d) -> (a, b) -> (c, d) And this appears now as a the classic f × g operation over pairs, implemented as (***) in Control.Arrow: (***) :: (a -> b) -> (c -> d) -> (a, b) -> (c, d) (f *** g) (x, y) = (f x, g y) (Actually the original is a little lazier, using irrefutable patterns on the pair.) Then you can do: (show *** show) ("string", True) And I suspect that's the best you'll get. There may be a wild solution involving typeclasses and existentials, but this doesn't seem altogether too bad. -- -David House, dmhouse@gmail.com

Marco Túlio Gontijo e Silva wrote:
is there a way to defined something as a map to use in tuples? I tried this:
mapTuple f (a, b) = (f a, f b)
But the type inferred to it is not as generic as I wanted:
mapTuple :: (t -> t1) -> (t, t) -> (t1, t1)
What you seem to want to do is impossible. Just want type would you want to assign to mapTuple? I bet you can't even express that in natural language, no wonder it's impossible in Haskell. Types that are possible, not completely useless, but still impossible to infer, could be: mapTuple :: (forall a . a -> a) -> (a,a) -> (a,a) mapTuple :: (forall a . a -> f a) -> (a,a) -> (f a, f a) (for suitable f or f in a suitable class) Most generalizations turn out to be useless, because there aren't any functions of the needed type that could be passed to mapTuple.
mapTuple show ("string", True)
So you want mapTuple :: forall c . (c a, c b) => (forall a . c a => a -> r) -> (a,b) -> (r,r) which infortunately is only pseudo-Haskell, since c would be a variable that ranges over type classes, and that doesn't exist. I guess you might be able to fake sauch a variable by explicitly passing a dictionary, but that's more complicated than passing the show function twice. So I'd recommend to just forget about it and live with mapTuple taking two functions. In that case you don't even need mapTuple, since it already exists under the name of (***) in Control.Arrow, along with other goodies. You could readily restrict mapTuple to the Show class, giving showTupleWith :: (Show a, Show b) => (forall a . Show a => a -> r) -> (a,b) -> (r,r) but there aren't that many functions it would accept as argument, mostly just show composed with something that operates on strings. -Udo -- If your life was a horse, you'd have to shoot it.

Udo Stenzel wrote:
Marco T?lio Gontijo e Silva wrote:
is there a way to defined something as a map to use in tuples? I tried this:
mapTuple f (a, b) = (f a, f b)
But the type inferred to it is not as generic as I wanted:
mapTuple :: (t -> t1) -> (t, t) -> (t1, t1)
What you seem to want to do is impossible. Just want type would you want to assign to mapTuple? I bet you can't even express that in natural language, no wonder it's impossible in Haskell.
Maybe some of the type experts could pipe up, but couldn't you express that as an intersection type? mapTuple :: ((a -> b) ^ (c -> d)) -> (a,c) -> (b,d) http://www.cs.cmu.edu/~rwh/theses/pierce.pdf Greg Buchholz

Is there anything in particular you're trying to accomplish? It seems like this is the type of thing you'd accomplish with typeclasses if you had a less general problem than you've presented. For example,
mapShowTuple :: (Show a, Show b) => (a, b) -> (String, String) mapShowTuple (x, y) = (show x, show y)
That said, it would be nice do be able to do something a little more general, but still with a specific typeclass, like
mapNumOpTuple :: (Num a, Num b) => (Num c => c -> c) -> (a, b) -> (a, b) mapNumOpTuple f (x, y) = (f x, f y)
(This unfortunately fails to typecheck; GHC chokes with "Illegal
polymorphic or qualified type". On the other hand, I'm still pretty
new to Haskell myself, so maybe someone else knows how to write this
correctly without doing complex type hackery.)
It would also be nice to be able to generalize over all typeclasses,
e.g. (pseudo-code here)
mapTypeclassOpTuple :: for all typeclasses C ((C a, C b) => (C c => c
-> c) -> (a, b) -> (a, b))
but I don't even know how that would fit into Haskell's syntax. I
suspect it's an idea that's been discussed, and I just don't know the
term for it.
Anyway, if you can make your problem more specific, it might be easier to solve.
--Grady
On 1/11/07, Marco Túlio Gontijo e Silva
Hello,
is there a way to defined something as a map to use in tuples? I tried this:
mapTuple f (a, b) = (f a, f b)
But the type inferred to it is not as generic as I wanted:
mapTuple :: (t -> t1) -> (t, t) -> (t1, t1)
Then I tried a different, but not much, implementation:
mapTuple' f g (a, b) = (f a, g b) mapTuple f = mapTuple' f f
But the inferred type was the same.
Is there a way to define a function in which I can be able to do something as this?
mapTuple show ("string", True)
-- malebria Marco Túlio Gontijo e Silva Correio (MSN): malebria@riseup.net Jabber (GTalk): malebria@jabber.org Telefone: 33346720 Celular: 98116720 Endereço: Rua Paula Cândido, 257/201 Gutierrez 30430-260 Belo Horizonte/MG Brasil
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 12/01/07, Grady Lemoine
Is there anything in particular you're trying to accomplish? It seems like this is the type of thing you'd accomplish with typeclasses if you had a less general problem than you've presented. For example,
mapShowTuple :: (Show a, Show b) => (a, b) -> (String, String) mapShowTuple (x, y) = (show x, show y)
That said, it would be nice do be able to do something a little more general, but still with a specific typeclass, like
mapNumOpTuple :: (Num a, Num b) => (Num c => c -> c) -> (a, b) -> (a, b) mapNumOpTuple f (x, y) = (f x, f y)
(This unfortunately fails to typecheck; GHC chokes with "Illegal polymorphic or qualified type". On the other hand, I'm still pretty new to Haskell myself, so maybe someone else knows how to write this correctly without doing complex type hackery.)
It's close: {-# OPTIONS_GHC -fglasgow-exts #-} mapNumOpPair :: (Num a, Num b) => (forall c. Num c => c -> c) -> (a, b) -> (a,b) mapNumOpPair f (x,y) = (f x, f y)
It would also be nice to be able to generalize over all typeclasses, e.g. (pseudo-code here)
mapTypeclassOpTuple :: for all typeclasses C ((C a, C b) => (C c => c -> c) -> (a, b) -> (a, b))
but I don't even know how that would fit into Haskell's syntax. I suspect it's an idea that's been discussed, and I just don't know the term for it.
That's an interesting idea, typeclass variables. It would require a bit of a kind system for typeclasses, but that's not so hard. I somehow doubt it would get used all *that* much though. Can anyone think of a clever way to apply this? - Cale

I knew there must be a way in GHC to do that second example!
As for the third example, it might be a slick way to do some
super-hyper-refactoring, but I admit I can't think of anything it
would be actually necessary for offhand.
--Grady
On 1/12/07, Cale Gibbard
On 12/01/07, Grady Lemoine
wrote: Is there anything in particular you're trying to accomplish? It seems like this is the type of thing you'd accomplish with typeclasses if you had a less general problem than you've presented. For example,
mapShowTuple :: (Show a, Show b) => (a, b) -> (String, String) mapShowTuple (x, y) = (show x, show y)
That said, it would be nice do be able to do something a little more general, but still with a specific typeclass, like
mapNumOpTuple :: (Num a, Num b) => (Num c => c -> c) -> (a, b) -> (a, b) mapNumOpTuple f (x, y) = (f x, f y)
(This unfortunately fails to typecheck; GHC chokes with "Illegal polymorphic or qualified type". On the other hand, I'm still pretty new to Haskell myself, so maybe someone else knows how to write this correctly without doing complex type hackery.)
It's close:
{-# OPTIONS_GHC -fglasgow-exts #-}
mapNumOpPair :: (Num a, Num b) => (forall c. Num c => c -> c) -> (a, b) -> (a,b) mapNumOpPair f (x,y) = (f x, f y)
It would also be nice to be able to generalize over all typeclasses, e.g. (pseudo-code here)
mapTypeclassOpTuple :: for all typeclasses C ((C a, C b) => (C c => c -> c) -> (a, b) -> (a, b))
but I don't even know how that would fit into Haskell's syntax. I suspect it's an idea that's been discussed, and I just don't know the term for it.
That's an interesting idea, typeclass variables. It would require a bit of a kind system for typeclasses, but that's not so hard. I somehow doubt it would get used all *that* much though. Can anyone think of a clever way to apply this?
- Cale
participants (8)
-
Arthur van Leeuwen
-
Cale Gibbard
-
David House
-
Grady Lemoine
-
Greg Buchholz
-
Marco Túlio Gontijo e Silva
-
minh thu
-
Udo Stenzel