[Haskell-cafe] type inference and named fields

Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk
Thu Jun 23 14:01:50 EDT 2005


I have discovered something I believe to be a problem in Haskell'98,
although it is not a simple bug as such - it has more of the flavour of
an unintended mismatch in the interaction of two separate features.
Since Haskell is deeply principled language, a feature conflict is
extremely rare, and so worthy of note.

So here it is:

Some attempts to use named field updates are prohibited by type
inference, even though the code is perfectly type safe.

Here is an example.

> module Fieldbug where
> data Fields a =
>     VariantWithTwo { field1 :: a
>                    , field2 :: a }
>   | VariantWithOne { field1 :: a }

The key point here is that the data structure with named fields has more
than one constructor, and some fields are omitted in one of the
variants.  Now let's try to write a simple conversion function over
values of this type, using only the named-field update style:

> data Void = Void
> 
> voidcast :: Fields a -> Fields Void
> voidcast v@(VariantWithTwo{}) = v { field1 = Void , field2 = Void }
> voidcast v@(VariantWithOne{}) = v { field1 = Void }

It looks simple enough doesn't it?  But none of the widely available
Haskell implementations will accept this code.

Hugs:
  ERROR "Fieldbug.hs":11 - Inferred type is not general enough
  *** Expression    : voidcast
  *** Expected type : Fields a -> Fields Void
  *** Inferred type : Fields Void -> Fields Void

ghc:
  Fieldbug.hs:11:32:
    Couldn't match the rigid variable `a' against `Void'
      `a' is bound by the type signature for `voidcast'
      Expected type: Fields Void
      Inferred type: Fields a
    In the record update: v {field1 = Void}
    In the definition of `voidcast':
        voidcast (v@(VariantWithOne {})) = v {field1 = Void}

nhc98:
  ======  Errors after type inference/checking:
  Derived type for Fieldbug.voidcast at 10:1-11:42 does not match due to:
    given free variable a is bound to Void
  Derived:((Fields Void) -> (Fields Void))
  Given  :((Fields a) -> (Fields Void))

As far as I can tell, the problem is that in the final line, the expression
    v { field1 = Void }
is interpreted by the type inference algorithm as if the variable v
could contain either constructor VariantWithOne or VariantWithTwo.
Obviously in the latter case the expression would indeed be incomplete
because it casts only one of the fields, not both.  But we know that
can never be the case!  By pattern-matching, this particular v /must/ be
the former constructor.  Unfortunately we cannot pass that knowledge
into the type inference algorithm.

It turns out that it is in fact /impossible/ to write this conversion
function using only named field updates.  It can only be written by
using an explicit constructor on the rhs, which thus forces you to
initialise all its fields explicitly.  This negates any value from using
named fields in the first place.

Regards,
    Malcolm


More information about the Haskell-Cafe mailing list