Records in Haskell

AntC anthony_clayden at clear.net.nz
Sat Mar 3 04:40:50 CET 2012


Isaac Dupree <ml <at> isaac.cedarswampstudios.org> writes:

> 
> >>
> >> In the meantime, I had an idea (that could work with SORF or DORF) :
> >>
> >> data Foo = Foo { name :: String } deriving (SharedFields)
> >>
> >> The effect is: without that "deriving", the declaration behaves just
> >> like H98.
> >>
> > Thanks Isaac, hmm: that proposal would work against what DORF is trying to 
do.
> >
> > What you're not getting is that DORF quite intentionally helps you hide the
> > field names if you don't want your client to break your abstraction.
> >
> > So under your proposal, a malicious client could guess at the fieldnames in
> > your abstraction, then create their own record with those fieldnames as
> > SharedFields, and then be able to update your precious hidden record type.
> 
> Show me how a malicious client could do that.  Under DORF plus my 
> mini-proposal,
> 
> module Abstraction (AbstractData) where
> data AbstractData = Something { field1 :: Int, field2 :: Int }
> ...
> --break abstraction how? let's try...
> 
> module Client1 where
> import Abstraction
> data Breaker = Something { field1 :: Int } deriving (SharedFields)
> -- compile fails because there are no field-labels in scope

Correct that the fieldLabel is not in scope, so that compile will fail; but 
what price did you pay?

Hint: what did you import with `Abstraction`?
Answer: you did not import `field1` selector function, nor the mechanism 
behind it.

So in module Client1 you can't access the `field1` content of a record type 
AbstractData. 

OK, that's sometimes something you want: to be able to pass around records of 
a specific type without allowing the client to look inside them at all.

But I was talking about the more common requirement for encapsulation. I want 
to control access to my record type: the client can read (certain) fields, but 
not update them. Other fields I don't want the client to even know about. 
(You've achieved the last part with your Client1, for all of the fields.)

(FYI: that's how wiki pages turn out so long; specifying exactly all the ins 
and outs at that sort of subtle detail.)

AntC






More information about the Glasgow-haskell-users mailing list