Function signatures and type class constraints

Hi, I'm wondering why I have to repeat the class constraints at every function. If I got the data type
data (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c = Foo a b c
and then a function from Foo to String I have to supply the signature
bar :: (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c -> String
even though it should be clear that a, b and c *must* fulfill the constraints already so I should be able to just supply the signature
bar :: Foo a b c -> String
Another related problem I got is that even though I can create the type
type B = (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c
I cannot use it like
bar :: B -> String
so my type class constraints got a tendency become huge! It is possible to work around this somehow? I'm in a situation at the moment where I got a data type with four fields each with three constraints (Show, Eq, Data), so I have to repeat 12 constraints at every function signature... :( Finally is there some way to bundle type class constraints, something like
data {Eq, Show, Data} {a, b, c} => Foo a b c = Foo a b c -- make believe syntax
so I don't have to repeat every constraint and variable all the time? -- Oscar

On Monday 23 August 2010 22:30:03, Oscar Finnsson wrote:
Hi,
I'm wondering why I have to repeat the class constraints at every function.
If I got the data type
data (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c = Foo a b c
Type class constraints on datatypes are considered a wart. They don't do what people expect, in particular they don't make the constraints available at the use site. It works if you move the constraints across the '=': {-# LANGUAGE ExistentialQuantification #-} data Foo a b c = (Eq a, Show a, ...) => Foo a b c or with GADT syntax: {-# LANGUAGE GADTs #-} data Foo x y z where Foo :: (Eq a, Show a, ...) => a -> b -> c -> Foo a b c Both make the constraints available at the use site, bar :: Foo a b c -> String bar (Foo a b c) = "Foo " ++ show a ++ " " ++ show b ++ " " ++ show c ++ ", Yay!"
and then a function from Foo to String I have to supply the signature
bar :: (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c -> String
even though it should be clear that a, b and c *must* fulfill the constraints already so I should be able to just supply the signature
One would think so. It's a wart.
bar :: Foo a b c -> String

Thanks for the tip. You saved my day (and code)!
So what is the point of having the constraint on the left side of the
'='? Will it allow me to do anything that the right-side constraint
won't?
-- Oscar
On Mon, Aug 23, 2010 at 11:06 PM, Daniel Fischer
On Monday 23 August 2010 22:30:03, Oscar Finnsson wrote:
Hi,
I'm wondering why I have to repeat the class constraints at every function.
If I got the data type
data (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c = Foo a b c
Type class constraints on datatypes are considered a wart. They don't do what people expect, in particular they don't make the constraints available at the use site.
It works if you move the constraints across the '=':
{-# LANGUAGE ExistentialQuantification #-}
data Foo a b c = (Eq a, Show a, ...) => Foo a b c
or with GADT syntax:
{-# LANGUAGE GADTs #-}
data Foo x y z where Foo :: (Eq a, Show a, ...) => a -> b -> c -> Foo a b c
Both make the constraints available at the use site,
bar :: Foo a b c -> String bar (Foo a b c) = "Foo " ++ show a ++ " " ++ show b ++ " " ++ show c ++ ", Yay!"
and then a function from Foo to String I have to supply the signature
bar :: (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c -> String
even though it should be clear that a, b and c *must* fulfill the constraints already so I should be able to just supply the signature
One would think so. It's a wart.
bar :: Foo a b c -> String

It uses less space. Conceptually:
data X a = Num a => ConX a
looks like this in memory: { ConX tag, a, proof of Num a } where the proof is usually a pointer to the dictionary for that typeclass at that type. Whereas
data Num a => Y a = ConY a
looks like this:
{ ConY tag, a }
This is why the rhs constraint lets you access methods of the
typeclass inside the function; pattern matching on ConX provides a Num
dictionary for the code to call. For ConY, it has to get that
dictionary from somewhere-- the caller has to pass it in.
-- ryan
On Wed, Aug 25, 2010 at 9:59 AM, Oscar Finnsson
Thanks for the tip. You saved my day (and code)!
So what is the point of having the constraint on the left side of the '='? Will it allow me to do anything that the right-side constraint won't?
-- Oscar
On Mon, Aug 23, 2010 at 11:06 PM, Daniel Fischer
wrote: On Monday 23 August 2010 22:30:03, Oscar Finnsson wrote:
Hi,
I'm wondering why I have to repeat the class constraints at every function.
If I got the data type
data (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c = Foo a b c
Type class constraints on datatypes are considered a wart. They don't do what people expect, in particular they don't make the constraints available at the use site.
It works if you move the constraints across the '=':
{-# LANGUAGE ExistentialQuantification #-}
data Foo a b c = (Eq a, Show a, ...) => Foo a b c
or with GADT syntax:
{-# LANGUAGE GADTs #-}
data Foo x y z where Foo :: (Eq a, Show a, ...) => a -> b -> c -> Foo a b c
Both make the constraints available at the use site,
bar :: Foo a b c -> String bar (Foo a b c) = "Foo " ++ show a ++ " " ++ show b ++ " " ++ show c ++ ", Yay!"
and then a function from Foo to String I have to supply the signature
bar :: (Eq a, Show a, Data a, Eq b, Show b, Data b, Eq c, Show c, Data c) => Foo a b c -> String
even though it should be clear that a, b and c *must* fulfill the constraints already so I should be able to just supply the signature
One would think so. It's a wart.
bar :: Foo a b c -> String
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Wednesday 25 August 2010 18:59:26, Oscar Finnsson wrote:
Thanks for the tip. You saved my day (and code)!
So what is the point of having the constraint on the left side of the '='?
I don't really know. What it does is preventing users from constructing values with arguments whose types don't satisfy the constraints. That probably seemed more useful before the experience than it really is. Says the report: http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-680004.2 "For example, the declaration data Eq a => Set a = NilSet | ConsSet a (Set a) introduces a type constructor Set of kind ∗→∗, and constructors NilSet and ConsSet with types NilSet :: ∀ a. Set a ConsSet :: ∀ a. Eq a ⇒ a → Set a → Set a In the example given, the overloaded type for ConsSet ensures that ConsSet can only be applied to values whose type is an instance of the class Eq. Pattern matching against ConsSet also gives rise to an Eq a constraint. For example: f (ConsSet a s) = a the function f has inferred type Eq a => Set a -> a. The context in the data declaration has no other effect whatsoever." ghci> case (NilSet :: Set (Int -> Bool)) of { NilSet -> True; _ -> False } True Note that the constraint doesn't apply to NilSet, because that constructor has no arguments (how the context on the data declaration is mapped to type class constraints on the constructors is explained in the report).
Will it allow me to do anything that the right-side constraint won't?
Nothing useful, as far as I know.
participants (3)
-
Daniel Fischer
-
Oscar Finnsson
-
Ryan Ingram