Records in Haskell

Gábor Lehel illissius at gmail.com
Fri Jan 20 17:18:18 CET 2012


2012/1/18 Simon Peyton-Jones <simonpj at microsoft.com>:
> | > Has *is* a type class. It can be used and abused like any other.
> | > Record members with the same key ought to have the same semantics; the
> | > programmer must ensure this, not just call them all "x" or the like.
> | >
> | > Weak types these are not. The selector type is well-defined. The value
> | > type is well-defined. The record type is well-defined, but of course
> | > we define a type-class to let it be polymorphic.
>
> I want to mention that the issue Greg raises here is tackled under "Representation hiding".
>
> The way we currently prevent random clients of a data type from selecting its "foo" field is by hiding the record selector "foo". Similarly for its data constructors. This is Haskell's way of doing data abstraction; it may not be the best way, but it's Haskell's way.
>
> The trouble with instance declarations is that they are *always* exported.  No hiding.
>
> Under "Representation hiding" I suggest that
>
> * If the record selector "foo" is in scope (by any name),
>  then the corresponding Has instance is in scope too
>  and vice versa.
>
> That would match up with Haskell's hiding mechanisms precisely, albeit at the cost of having an ad-hoc rule for "Has" instances.
>
> Simon
>

I think these are separate issues. To use the analogy with functions
again, imagine we could do this:

module A where
data Foo = Foo

foo :: Foo -> Int
foo Foo = 9

module B where
bar :: HasFunction a "foo" (a -> Int) => a -> Int
bar a = foo a

module Main where
import A
import B
main = print $ bar Foo

Would we like it?

The problem isn't that you can access unexported functions (though
that would also be a problem), the problem is that you're overloading
functions based on only their name and type, and the "foo" you find
might have a different meaning from the one you expected. With type
classes, we have a mechanism to ensure that code at point A and code
at point B are using the same assumptions. If you declare an instance
and it doesn't match the assumptions set out for the class, it's a
programmer error. But you can't realistically say "don't declare a
function with this name and type unless you mean the same thing by it
that I mean by it". If we want similar safety for record fields, we
could use a similar mechanism. (Again, without addressing the question
of what we want, because I don't know.)



More information about the Glasgow-haskell-users mailing list