[Haskell-cafe] RealFloat constraint on Complex type

Bryan O'Sullivan bos at serpentine.com
Wed May 21 09:54:37 EDT 2008


Richard A. O'Keefe wrote:

>> I think the practice of constraint in type definitions is generally
>> discouraged,
> 
> Is this true?  If so, why?

As a practical matter, a Haskell 98 constraint infects every place you
might like to use the type.  They're like prion proteins, corrupting
everything they touch, replicating implacably as they go.

Here's the usual pattern that leads to the abandonment of constraints on
types by the previously innocent coder.  You add the constraint in the
one place you think you need it, only to find that the type checker
insists that three more are now required on previously pristine code
that otherwise never mentions your type.  You reluctantly add the
constraint to those, and the compiler demands another seven uses.  Now
your code is littered with meaningless spaghetti constraints that
obfuscate your original intent.

The same contagion also costs you the ability to derive instances of
many useful built-in typeclasses, such as Functor.  The constraint on
the type requires that a function such as fmap must have the constraint,
too, and thus the plague continues.

Pre-GADT syntax doesn't have this problem.

  {-# LANGUAGE GADTs #-}

  data Foo a = Show a => Foo a

  foo :: Foo a -> a
  foo (Foo a) = a

Notice the change in the location of the constraint, and the lack of a
need for a constraint on the function foo.  Real GADTs avoid the problem
in a similar way.

  data Bar a where
      Bar :: Show a => a -> Bar a

  bar :: Bar a -> a
  bar (Bar a) = a


More information about the Haskell-Cafe mailing list