
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