[Haskell-cafe] A backwards-compatible record proposal
Brian Hulley
brianh at metamilk.com
Sat Aug 19 16:46:52 EDT 2006
Bernard James POPE wrote:
> On Sat, Aug 19, 2006 at 09:21:34AM +0100, Brian Hulley wrote:
>> Therefore I think the desugaring would need to take place in the
>> compiler so the compiler could avoid exporting the
>> compiler-generated instances when the fields are not present in the
>> module export list.
>
> I'm not entirely sure I understand you here,
For example,
module M (Rec) where
data Rec a = Rec {f :: a}
means that the components of Rec are visible in module M but not from any
other module ie Rec is an abstract data type. However if a dotted field was
used, as in:
module M (Rec) where
data Rec a = Rec {.f :: a}
we'd also like the fields of Rec to be inaccessible from outside, but since
(.f) is a global typeclass, and module M contains an instance of (.f) (Rec
a) a, and since any module which imports M always sees all instances that M
sees, in particular it would see the instance (.f) (Rec a) a and therefore
be able to inspect values of (Rec a) thus breaking the module abstraction
barrier.
The problem is that the inability to prevent instances from being exported
from a module breaks the abstraction, so all though everything in the
proposal can be desugared into plain Haskell (with MPTC/FD) the caveat is
that we would lose abstraction with this simple method.
However I think it could be solved by a more complex desugaring:
module M (Rec, use) where
data Rec a = Rec {f :: a}
use :: Rec a -> (a,a)
use r = (r.f, r.f)
by introducing a newtype and adding wrappers to functions as follows:
module M (Rec, use) where
import DotClasses.Dot_f -- every class has its own module (*)
data Rec' a = Rec a
newtype Rec a = Rec (Rec' a)
instance Dot__f (Rec' a) a where
__dot_f (Rec' x) = x
use :: Rec a -> (a,a)
use (Rec r) = use' r
use' :: Rec' a -> (a,a)
use' r = (r.f, r.f)
All code in the source module that uses Rec is renamed to syntactically
isomorphic code using Rec' instead, and exported functions are replaced by
wrappers to renamed versions of the original functions. Any code outside the
module can only see Rec and not Rec' so the abstraction is preserved.
> but something to
> consider is how well the sytem can be handled by something which is
> not a compiler, but a code transformer. Something like Hat or buddha.
>
> For tools like these, it is important that a desugared program is
> still a valid (source level) program. (Haskell 98 is close to this,
> but not 100% - unfortunately).
>
> Desugaring sometimes introduces new code into a program (for instance
> the deriving rules), a program transforming tool will most likely
> have to apply its transformation to that introduced code. Therefore,
> to transform a Haskell program you have to desugar it (somewhat)
> first. We want
> the result to remain a valid Haskell program, so it can be accepted by
> an ordinary compiler.
With the more complex desugaring described above the result would be
ordinary Haskell code (though not H98 due to MPTC and FD for the Dot_*
classes).
(*) Since it might be unwieldy to try to build a single module containing
all the dot classes used in an entire program and all libraries, a simple
solution is to just have a separate directory to store dot classes then the
rule would be when the desugaring tool encounters a dotted field in a data
decl, it would check to see if the module DotClasses.Dot_f already exists,
and if it doesn't, then it would create the module:
module DotClasses.Dot_f where
class Dot_f a b | a -> b
__dot_f :: a -> b
Each dotted field that appears in any code in a module would give rise to an
import DotClasses.Dot_ directive.
(If the module used libraries that were not also desugared then the "ensure
Dot_ module created" operation would have to be done for all dotted fields
used anywhere in the module, not just in data decls.)
Thus there appears to be a fairly straightforward algorithm for desugaring
to code that could be readily accepted without needing to change the
compiler (or other tools) after all. Of course the usefulness of error
messages etc would be improved if the tools could deal with unsugared
source.
Best regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.
http://www.metamilk.com
More information about the Haskell-Cafe
mailing list