First class labels

Claus Reinke claus.reinke at talk21.com
Fri Feb 10 09:13:42 EST 2006


| the concrete proposal is to address one of these remaining issues,
| namely how to identify record field labels as such. for that, I
| outlined three options, although that outline perhaps wasn't concrete 
| enough:
| 
| 1. make label declarations unneccessary (eg., #pointX :: #PointX)

effect on the type system: a new (meta-)rule for a new kind of 
literal constants: whenever we see something looking like 
" '#'<identifier> ", its type is " '#'<Identifier>".

Essentially the same as for other literals: whenever we see
something looking like " [0-9]+ ", its type is " Num a => a ". 
whenever we see " True ", its type is " Bool ", etc. .

Similar to numeric literals, there'd be no place in source where
all those literals/labels are declared, but literals of the same type 
in different modules would be compatible. So this would work
without problems:

    module A
    main = #pointX

    module B
    main = #pointX

    module C
    import A
    import B
    main = print [A.main,B.main]

| 2. make type sharing expressible (something like the sharing
|     constraints in Standard ML's module language, to allow you to
|     say when two declarations from different imports refer to the
|     same type)

this is definitely a type system issue. if we have

    module A where 
    data PointX = PointX deriving Show
    main = print PointX

    module B where 
    data PointX = PointX deriving Show
    main = print PointX

    module C -- this doesn't work!
    import A
    import B
    main = print PointX -- conflict here! ambiguous occurrence..

we have a problem. in a simple form, the sharing constraints I 
had in mind would permit us to express which structurally equivalent 
declarations define *the same type*. that is, module C would be

    module C
    import A
    import B
    sharing A.PointX B.PointX
    main = print PointX 
                -- no conflict, A.PointX and B.PointX have been 
                -- identified, refer to the same type

the type system would need to unify the shared types. to make 
that safe, it would need to check for structural equivalence of the
declarations when encountering a sharing constraint; if successful, 
both shared types would afterwards be seen as synonyms for 
one and the same type.

A very minimal version of this option would suffice for labels;

in general, this kind of sharing constraints is non-trivial, but useful
(if we could share classes and instances defined multiple times,
like the instances for (,,,,,,,,,,,) discussed in other threads).

| 3. introduce a least upper bound for shared label imports
|     (so A and B could just 'import Data.Label(pointX)', which
|      would magically provide the shared declaration for pointX)

with this option, the modules would look like this

    module A
    import Data.Label(pointX)

    module B
    import Data.Label(pointX)
    
    module C
    import A
    import B
    main = print pointX 
                -- no conflict, A.pointX and B.pointX are the same

this would have a similarly small effect on the type system as option 1,
only that instead of syntax, we'd use imports from the reserved module
'Data.Label' to identify what is a label and what is not.

whenever encountering an ' import Data.Label(<identifier>) ', we
interpret ' Data.Label.<identifier> ' as a constant of type 
' Data.Label.<Identifier> ' and ' <identifier> ' as a constant of
type ' <Identifier> '. the difference to normal imports is that the
compiler/type system needs to know about 'Data.Label'.

In other words, 'Data.Label' does not exist in source or object code,
but as a hint for the compiler/type system. Any identifier imported from
there is a label of its own type, nothing else can be imported from there.

sorry for being so difficult to understand. the questions help.

cheers,
claus



More information about the Haskell-prime mailing list