[Haskell-cafe] type inference and named fields

Henning Thielemann lemming at henning-thielemann.de
Thu Jun 23 14:43:33 EDT 2005


On Thu, 23 Jun 2005, Malcolm Wallace wrote:

> > 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.

This is either a point against multiple fields with the same label or
against the field update syntax. Against multiple declarations because it
is not allowed to define multiple objects with the same name in the same
scope. But if you consider multiple occurences of the same field name as
distributed declarations of the same function the conflict is resolved.
 So it seems to be more a point against the record update syntax. What I
need quite often is a function which updates a field. This would nicely
work also for your example.

update_field1 :: (a -> a) -> Fields a -> Fields a
update_field1 f (VariantWithTwo x y) = VariantWithTwo (f x) y
update_field1 f (VariantWithOne x)   = VariantWithOne (f x)

(update_field1 (const x)) would replace a field value with a new one.

Support for this kind of update would be better than support by the
current update syntax.



More information about the Haskell-Cafe mailing list