[Haskell] Re: (small) records proposal for Haskell '06

oleg at pobox.com oleg at pobox.com
Fri Jan 6 02:14:18 EST 2006


David Roundy wrote:
> The only solution I can imagine
> would be to implement a class for each field name.  i.e. the only reasonble
> type of f I can imagine is something like
>
> f :: Integral i, RecordHasField_foo i r => r -> r
>
> But that's a very complicated solution, and once one implemented that
> solution, one would no longer need to remove the accessor functions (since
> they could be stuck in the class), which would obsolete this whole idea...

There is no need to speak of this solution in subjunctive mood. It
*has* been implemented. If you wish, you can try at right now, with the
existing GHC (e.g., 6.2, 6.4 or 6.4.1), using the Cabal distribution
of HList/OOHaskell very kindly made by Einar Karttunen. Here's an example:

> {-# OPTIONS -fglasgow-exts #-}
> {-# OPTIONS -fallow-undecidable-instances #-}
>
> module Test where
>
> import OOHaskell -- big overkill but convenient: it's only one line...
>
> accessor r f = r # f
>
> setter r f v = r . at . (f,v)

	*Test> :t accessor
	accessor :: (HasField l r v) => r -> l -> v

Couldn't be any simpler...

	*Test> :t setter
	setter :: (HZip x l' l,
		   HUpdateAtHNat n b y l',
		   HFind a x n,
		   HZip x y r) =>
		Record r -> a -> b -> Record l

Admittedly, that type can be simpler (just as the type of the
accessor). But the getter is optimized (including its type) because
we use it all the time. The setter is based on a generic (and hence
less optimal) code. I guess we don't use setters often, so we never
got around to making even trivial optimizations... Something to do for
the next Haskell Community Report.





More information about the Haskell mailing list