
I would like to have tuple (f1,f2) x = (f1 x, f2 x) tuple (f1,f2,f3) x = (f1 x, f2 x, f3 x) tuple (f1,f2,f3,f4) x = (f1 x, f2 x, f3 x, f4 x) ... I'm aware of Control.Arrow and the &&& combinator, and I can use that instead, but f1 &&& f2 &&& f3 doesn't have _exactly_ the type I want. What should I do?

On Wed, 2011-09-14 at 13:35 +1200, Richard O'Keefe wrote:
I would like to have
tuple (f1,f2) x = (f1 x, f2 x) tuple (f1,f2,f3) x = (f1 x, f2 x, f3 x) tuple (f1,f2,f3,f4) x = (f1 x, f2 x, f3 x, f4 x) ...
I'm aware of Control.Arrow and the &&& combinator, and I can use that instead, but f1 &&& f2 &&& f3 doesn't have _exactly_ the type I want.
What should I do?
There is no polymorphism across tuple structures, so if you absolutely *must* have n-tuples instead of nested 2-tuples, then you just need to implement the new functions as needed. You can't implement that only once. Plenty of places in base do this, especially for instances. -- Chris Smith

On 14/09/2011, at 1:44 PM, Chris Smith wrote:
On Wed, 2011-09-14 at 13:35 +1200, Richard O'Keefe wrote:
I would like to have
tuple (f1,f2) x = (f1 x, f2 x) tuple (f1,f2,f3) x = (f1 x, f2 x, f3 x)
There is no polymorphism across tuple structures,
I know that. I know how tuples get to be instances of Ix, one instance declaration for each of (,) (,,) (,,,) ....
so if you absolutely *must* have n-tuples instead of nested 2-tuples, then you just need to implement the new functions as needed. You can't implement that only once.
I don't *expect* to implement anything just once. I am perfectly happy writing as many instance declarations as I have tuple sizes that I care about. It's just that I can't see how to get the types right, because in class Thingy t ... where tuple :: t -> a -> b b depends on t and possibly a, so instance Thingy (,,) where tuple (f,g,h) x = (f x, g x, h x) it's not an arbitrary b. Can this be done with functional dependencies?

On Wed, 2011-09-14 at 13:56 +1200, Richard O'Keefe wrote:
I don't *expect* to implement anything just once. I am perfectly happy writing as many instance declarations as I have tuple sizes that I care about.
Ah, okay... then sure, you can do this: class Tuple a b c | a b -> c where tuple :: a -> b -> c instance Tuple (a -> b, a -> c) a (b,c) where tuple (f,g) x = (f x, g x) and so on... You'll need fundeps (or type families if you prefer to write it that way), and probably at least flexible and/or overlapping instances, too, but of course GHC will tell you about those. -- Chris Smith

On Tue, Sep 13, 2011 at 10:03 PM, Chris Smith
Ah, okay... then sure, you can do this:
class Tuple a b c | a b -> c where tuple :: a -> b -> c
instance Tuple (a -> b, a -> c) a (b,c) where tuple (f,g) x = (f x, g x)
This wouldn't actually work well in practice. There's no dependency between the various occurrences of "a" in the types, so unless they're already known to be the same, GHC will complain about an ambiguous instance (please excuse the silly GHCi prompt): Ok, modules loaded: Tupling. ∀x. x ⊢ tuple ((+3), show) 4 <interactive>:0:1: No instance for (Tuple (a0 -> a0, a1 -> String) b0 c0) arising from a use of `tuple' Given that the class is only intended to be used where those types are equal, you really want it to unify them based on use of the tuple function.
and so on... You'll need fundeps (or type families if you prefer to write it that way), and probably at least flexible and/or overlapping instances, too, but of course GHC will tell you about those.
I rather prefer type families in this case, both because the problem is easily expressed in "type function" style, and because it gives you an easy type equality constraint to use, rather than using arcane trickery with overlaps to force post-hoc unification. We'd probably want to do something like this: class Tuple t where type Arg t :: * type Result t :: * tuple :: t -> Arg t -> Result t instance (x1 ~ x2) => Tuple (x1 -> a, x2 -> b) where type Arg (x1 -> a, x2 -> b) = x1 type Result (x1 -> a, x2 -> b) = (a, b) tuple (f, g) x = (f x, g x) instance (x1 ~ x2, x2 ~ x3) => Tuple (x1 -> a, x2 -> b, x3 -> c) where type Arg (x1 -> a, x2 -> b, x3 -> c) = x1 type Result (x1 -> a, x2 -> b, x3 -> c) = (a, b, c) tuple (f, g, h) x = (f x, g x, h x) Used like so: Ok, modules loaded: Tupling. ∀x. x ⊢ tuple ((+2), show, (< 2)) 3 (5,"3",False) Note that not only does this avoid ambiguity, it even unifies ambiguous types that are then defaulted by the usual means. That said, I question the utility of a class like this. The boilerplate instances are tedious to write and it's not flexible in any way; tuples not being defined inductively makes them a real pain to work with unless there's a particularly good reason to do so. Something equivalent to right-nested (,) with () as a terminator is much more pleasant, and since we're deep in the pits of non-portability anyway, might as well pull out bang patterns and UNPACK pragmas if avoiding extra bottoms was the reason for using plain tuples. - C.

On Wed, Sep 14, 2011 at 6:45 AM, Casey McCann
On Tue, Sep 13, 2011 at 10:03 PM, Chris Smith
wrote: Ah, okay... then sure, you can do this:
class Tuple a b c | a b -> c where tuple :: a -> b -> c
instance Tuple (a -> b, a -> c) a (b,c) where tuple (f,g) x = (f x, g x)
This wouldn't actually work well in practice. There's no dependency between the various occurrences of "a" in the types, so unless they're already known to be the same, GHC will complain about an ambiguous instance (please excuse the silly GHCi prompt):
Ok, modules loaded: Tupling. ∀x. x ⊢ tuple ((+3), show) 4
<interactive>:0:1: No instance for (Tuple (a0 -> a0, a1 -> String) b0 c0) arising from a use of `tuple'
Given that the class is only intended to be used where those types are equal, you really want it to unify them based on use of the tuple function.
and so on... You'll need fundeps (or type families if you prefer to write it that way), and probably at least flexible and/or overlapping instances, too, but of course GHC will tell you about those.
I rather prefer type families in this case, both because the problem is easily expressed in "type function" style, and because it gives you an easy type equality constraint to use, rather than using arcane trickery with overlaps to force post-hoc unification. We'd probably want to do something like this:
class Tuple t where type Arg t :: * type Result t :: * tuple :: t -> Arg t -> Result t
instance (x1 ~ x2) => Tuple (x1 -> a, x2 -> b) where type Arg (x1 -> a, x2 -> b) = x1 type Result (x1 -> a, x2 -> b) = (a, b) tuple (f, g) x = (f x, g x)
instance (x1 ~ x2, x2 ~ x3) => Tuple (x1 -> a, x2 -> b, x3 -> c) where type Arg (x1 -> a, x2 -> b, x3 -> c) = x1 type Result (x1 -> a, x2 -> b, x3 -> c) = (a, b, c) tuple (f, g, h) x = (f x, g x, h x)
Used like so:
Ok, modules loaded: Tupling. ∀x. x ⊢ tuple ((+2), show, (< 2)) 3 (5,"3",False)
Note that not only does this avoid ambiguity, it even unifies ambiguous types that are then defaulted by the usual means.
That said, I question the utility of a class like this. The boilerplate instances are tedious to write and it's not flexible in any way; tuples not being defined inductively makes them a real pain to work with unless there's a particularly good reason to do so. Something equivalent to right-nested (,) with () as a terminator is much more pleasant, and since we're deep in the pits of non-portability anyway, might as well pull out bang patterns and UNPACK pragmas if avoiding extra bottoms was the reason for using plain tuples.
I've just tried another approach (code below). And GHC even inferred type for tupleF. But I think GHC inferred the wrong type and I can't formulate the right one, it seems to require infinite number of constraints. With GHC inferred type this function is not usable, though: *Tuples> tupleF ((+2), show, (<2)) 3 <interactive>:1:0: Couldn't match expected type `TTail (a -> a, a1 -> String, a2 -> Bool)' against inferred type `(a -> a, a1 -> String, a2 -> Bool)' NB: `TTail' is a type function, and may not be injective When generalising the type(s) for `it' {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE FlexibleContexts #-} module Tuples where class Tuple t class (Tuple t, Tuple (TTail t)) => NTuple t where type THead t :: * type TTail t :: * thead :: t -> THead t ttail :: t -> TTail t tcons :: THead t -> TTail t -> t newtype Tuple1 a = Tuple1 a instance Tuple () instance Tuple (Tuple1 a) instance NTuple (Tuple1 a) where type THead (Tuple1 a) = a type TTail (Tuple1 a) = () thead (Tuple1 a) = a ttail (Tuple1 a) = () tcons a b = Tuple1 a instance Tuple (a, b) instance NTuple (a, b) where type THead (a, b) = a type TTail (a, b) = Tuple1 b thead (a, b) = a ttail (a, b) = Tuple1 b tcons a (Tuple1 b) = (a, b) instance Tuple (a, b, c) instance NTuple (a, b, c) where type THead (a, b, c) = a type TTail (a, b, c) = (b, c) thead (a, b, c) = a ttail (a, b, c) = (b, c) tcons a (b, c) = (a, b, c) tupleF t a = thead t a `tcons` tupleF (ttail t) a -- Victor Nazarov

On Wed, Sep 14, 2011 at 9:32 AM, Victor Nazarov
I've just tried another approach (code below). And GHC even inferred type for tupleF. But I think GHC inferred the wrong type and I can't formulate the right one, it seems to require infinite number of constraints. With GHC inferred type this function is not usable, though:
GHC can't actually infer your type with that implementation of tcons. There's no way for it to get from the arguments "THead t" and "TTail t" to the tuple type t, because (unlike type constructors) type families aren't necessarily injective, so there could be more than one type "t" that THead and TTail map to the types received. Furthermore, the open world assumption for type families means that even if there's only one valid "t" in scope, it can't simply select that because it must account for the possibility of more instances being introduced in other scopes. On the other hand, it can get from "t" to "THead t" and "TTail t" just fine, so if you give a type annotation that fixes the result type it should work. But that can be clumsy for actual use. The above issue is exactly why the implementation that I gave uses a slightly peculiar approach to calculate the other types based only on the type of the tuple argument. A slightly more complicated approach could probably be used to get some inference going in both directions, but in most cases the direction I gave will be what you want most. That said, the essential idea of what you're trying to do is a good one. Why not try separating the steps, though? Use one type family to give a bijection between standard tuples and some sort of right-nested pair representation (which is easy to infer both ways), then use standard type-level recursion to process the latter form however you like. You can do generic equivalents of map, fold, zip, &c. this way pretty easily. - C.

On 14/09/2011, at 2:45 PM, Casey McCann wrote:
class Tuple t where type Arg t :: * type Result t :: * tuple :: t -> Arg t -> Result t
instance (x1 ~ x2) => Tuple (x1 -> a, x2 -> b) where type Arg (x1 -> a, x2 -> b) = x1 type Result (x1 -> a, x2 -> b) = (a, b) tuple (f, g) x = (f x, g x)
That's it, that's what I was after. Thanks.

Using fundeps I came up with this:
class T funs arg res | funs -> arg res, arg res -> funs where
tuple :: funs -> arg -> res
instance (a ~ a0, a0 ~ a1) => T (a0 -> b, a1 -> c) a (b, c) where
tuple (f, g) a = (f a, g a)
instance (a ~ a0, a0 ~ a1, a1 ~ a2) => T (a0 -> b, a1 -> c, a2 -> d) a
(b, c, d) where
tuple (f, g, h) a = (f a, g a, h a)
Intuitively it seems to be exactly the same as the type families'
aproach, and looks quite clear too.
On 9/15/11, Richard O'Keefe
On 14/09/2011, at 2:45 PM, Casey McCann wrote:
class Tuple t where type Arg t :: * type Result t :: * tuple :: t -> Arg t -> Result t
instance (x1 ~ x2) => Tuple (x1 -> a, x2 -> b) where type Arg (x1 -> a, x2 -> b) = x1 type Result (x1 -> a, x2 -> b) = (a, b) tuple (f, g) x = (f x, g x)
That's it, that's what I was after. Thanks.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Markus Läll

On Thu, Sep 15, 2011 at 7:51 AM, Markus Läll
Intuitively it seems to be exactly the same as the type families' aproach, and looks quite clear too.
Not exact, no--as written, it's strictly more powerful. Your fundeps go in both directions, whereas the type families didn't (though could easily be extended to do so, if desired, at the cost of some extra verbosity). The main argument in favor of type families here is the ~ equality constraint which, as you've found, works in combination with fundeps as well. :] You can actually simulate it with fundeps alone, but you probably don't want to. All else equal I personally find type families easier to work with, but in this case the difference is minimal. For bidirectional constraints and simple transformations, fundeps are probably a bit nicer, so in hindsight I think yours is the better idea here. - C.
participants (5)
-
Casey McCann
-
Chris Smith
-
Markus Läll
-
Richard O'Keefe
-
Victor Nazarov