
On 03/01/2012 01:46 AM, AntC wrote:
Isaac Dupree
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.
(For super flexibility, allow to specify which fields are shared, like "deriving(SharedFields(name, etc, etc))" perhaps.)
Is it too verbose? Or too terrible that it isn't a real class (well, there's Has...)?
-Isaac
Thanks Isaac, hmm: that proposal would work against what DORF is trying to do.
You're right about the `deriving` syntax currently being used for classes. The fact of re-purposing the surface syntax is really no different to introducing different syntax.
[...]
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 } {- or it could use shared field names (shared privately) : fieldLabel field1 --however it goes fieldLabel field2 --however it goes data AbstractData = Something { field1 :: Int, field2 :: Int } deriving (SharedFields) -} module Client where import Abstraction --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 module Client2 where import Abstraction fieldLabel field1 --however it goes data Breaker = Something { field1 :: Int } deriving (SharedFields) -- succeeds, still cannot access AbstractData with Client2.field1 module Client3 where import Abstraction -- (using standalone deriving, if we permit it for SharedFields at all) deriving instance SharedFields AbstractData -- compile fails because not all constructors of AbstractData are in scope All my mini-proposal does is modify SORF or DORF to make un-annotated records behave exactly like H98. AntC (in an unrelated reply to Ian) :
I prefer DORF's sticking to conventional/well-understood H98 namespacing controls.
[warning: meta-discussion below; I'm unsure if I'm increasing signal/noise ratio] Since this giant thread is a mess of everyone misinterpreting everyone else, I'm not sure yet that DORF's namespacing is well-understood by anyone but you. For example, one of us just badly misinterpreted the other (above; not sure who yet). Would IRC be better? worse? How can the possibly-existent crowd of quiet libraries@ readers who understand SORF/DORF/etc. correctly show (in a falsifiable way) that they understand? any ideas? Do people misinterpret DORF this much because you posted at least 4000 words[1] without creating and making prominent a concise, complete description of its behaviour? (is that right?) I propose that any new record system have a description of less than 250 words that's of a style that might go in the GHC manual and that causes few if any misinterpretations. Is that too ambitious? Okay, it is. So. Differently, I propose that any new record system have a description of less than 500 words that completely specifies its behaviour and that at least half of libraries@ interprets correctly. (It's fine if the description refers to docs for other already-implemented type-system features, e.g. MPTCs and kind stuff.[2] ) Should we be trying for such a goal? (For reference: just SORF's "The Base Design" section is 223 words, and just DORF's "Application Programmer's view" only up to "Option One" is 451 words. (according to LibreOffice.) Neither one is a complete description, but then, my proposed "500 word description" wouldn't mention design tradeoffs. A GHC User's Guide subsection I picked arbitrarily[3] is 402 words.) [1] I counted the main DORF page plus the one you pointed me to, each of which is about 2000: http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFie... + http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFie... [2] My sense is that "(customer_id r) uses familiar type instance resolution [...]" is only a precise enough statement if the user declared the exact, unedited type of customer_id; and that having constraints like "r{ customer_id :: Int }" would need explanation in terms of familiar type inference such as classes. e.g... in a way that would explain "r{ SomeModule.customer_id :: Int }" (is that allowed?). I could try to write such a description and you could tell me where I go wrong... [3] "Record field disambiguation" http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/syntax-extns.html#dis... -Isaac