[Haskell-cafe] Function signatures and type class constraints

Daniel Fischer daniel.is.fischer at web.de
Mon Aug 23 17:06:05 EDT 2010


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
>


More information about the Haskell-Cafe mailing list