Records in Haskell

Johan Tibell johan.tibell at gmail.com
Wed Jan 18 18:43:31 CET 2012


On Mon, Jan 16, 2012 at 2:32 AM, Simon Peyton-Jones
<simonpj at microsoft.com> wrote:
> Johan, if you are serious, do add a new wiki page to describe the design.

I haven't thought trough the issues enough to describe the design just
yet. At the moment I prefer to discuss a little more to gain some more
clarity/insight.

> You say it's simple, but I don't think it really is.  The whole qualified name story is *already* pretty complicated: see http://ogi.altocumulus.org/~hallgren/hsmod/Description.pdf

I will definitely read this.

> Particular issues I can think of immediately:
>
> 1. What about data families
>
>        data instance T [a] = MkT { x :: Int }
>        data instance T Bool = T2 { x :: Bool }

I haven't really considered data families (and probably a bunch of
other extensions.) Since data families are type functions it seems to
me that to resolve 'x' we would also consider its type. At that point
you might say we should just do (B).

> What are the qualifies names for the two x's?
>
> 2.  Module exports.  What about
>
>        module M( S(..), T(..) ) where
>          data S = MkS { x :: Int }
>          data T = MkT { x :: Int }

The general idea is to treat a data type declaration

    data T = C { x :: t }

as a declaration containing a local module:

    data T = C { module T { x :: t } }

This is not unlike how OO languages do namespacing for classes and
modules e.g. in Java

    package foo;

    class C {
        int x;  // Static variable
    }

you can then say foo.C.x.

> When you import M, what comes into scope?

The qualified names S.x and T.x. This might not play well with our
module system though. We generally don't allow you to export or import
name*spaces* e.g.

    module M where
    import Data  -- contains e.g. Data.Text, Data.Map, etc

    f = Text.concat

In other words: our hierarchical modules system isn't very
hierarchical in that you can only mention leaf nodes. We could (I
think) get rid of all the dots in our modules names without changing
the semantics.

> 3. If you import the record field without the type name (currently possible) does that make the record field impossible to disambiguate?  Or is it still ok to disambiguate it with the type name.

I'd say no to the latter. It should probably be an import error. I'm
not sure how we can maintain backwards compatibility (i.e. also
exporting record fields as top-level identifiers, given you module
example above) under this proposal.

Cheers,
Johan



More information about the Glasgow-haskell-users mailing list