[Haskell] Per-type function namespaces (was: Data.Set whishes)

Conor McBride c.t.mcbride at durham.ac.uk
Thu Mar 4 13:58:15 EST 2004


Hi

While we're talking about SML, I think there are a few other things
worth stealing...


1) I still miss multiline pattern matching in lambda

  (fn p1 => e1 | p2 => e2 | ...)

not strictly necessary, but often less disruptive of the text than
either a let/where-introduced helper-function or \ x -> case x of ...
especially when there's more than one argument.

Doubtless there's some deep reason why Haskell doesn't have these
that I'm too young to remember.


2) I miss local implementation-decls in interface-decls end

Is there some fabulous layout rule for `where' clauses that means
the same thing?


3) I miss `open' from the module system. This allows

  let open Structure in expression end
  local open Structure in declarations end

reducing your program's acne. I often wonder why the OO world has
no room for Pascal's lovely old `with ... do ...'. [Pascal even
had variant records with case expressions: it wasn't remotely
type-safe, but it looked like datatypes. What happened to them?
Programmers like sums, but software engineers like products...]


Haskell already has per-module namespaces; everything has a unique
long name; good start. Now what we need is more control over the
meaning of short names. Could we have local opening of (already
imported) modules, simply rebinding the relevant short names in
their scope? You'd get the localized namespace you might want
at the cost of one scoped declaration, rather than a zillion
projections.

And while we're at it...

> Simon Peyton-Jones wrote:
> >
> > If the big bug-bear is record selectors, let's focus on them
> > exclusively.  I now think that ML got it right. ML records are simply
> > labelled tuples.

The pattern-matching was always dreadful, especially if you just
wanted to tweak one field, but I expect that could be dealt with.

Andreas Rossberg wrote:
> 
> Note that this is true only for SML, not for Caml.
> 
> > So just as (Bool,Int) is an anonymous type, so is
> > {x::Bool, y::Int}.  Indeed (Bool,Int) is just shorthand for {#1::Bool,
> > #2::Int}.
> 
> A bit of nitpicking: (Bool,Int) would be shorthand for {1::Bool,2::Int}.
> In SML, labels may be numeric or alpha-numeric. OTOH, the hash is the
> projection operator (ASCII art for \pi), which can be used for both
> kinds of labels:
> 
>    #2 (x,y,z)
>    #b {a=x, b=y, c=z}
> 
> Actually, #l is just syntactic sugar for (\{l=x,...}->x), which implies
> that you might need type annotations.

That's a neat piece of syntax, but if you're willing to look at types,
you might be able to introduce an opening operator for records,
<| say, at the cost of restricting field labels to being valid names.
ie if

  r :: {a::A, b::B, c::C}

  r <| e   means let {a=a,b=b,c=c} = r in e

Again, the usual projection is a special case.

No reason why you couldn't use this opening notation for the existing
field-labelled datatypes. OK, you'd be shadowing projection functions
with field names, but that's not so shocking.

This opens a further, if questionable, possibility, viz

  data MyQuad = MyQuad {a::Int, b::Int, c::Int} <|
                  f x = (a * x + b) * x + c

declaring a computed field f for that constructor. As usual, only your
conscience prevents you misusing this facility in a multi-constructor
type. For backward compatibility, you'd need to leave a, b and c as
global names, but you could choose to make f accessible only on opening.
That leaves open the possibility of

  data MyQuad = MyQuad {globa::Int, globb::Int, globc::Int} <|
                  a = globa
                  b = globb
                  c = globc
                  f :: Int -> Int
                  f x = (a * x + b) * x + c

which I'm sure could be sugared to

  data MyQuad = MyQuad {<| a::Int, <| b::Int, <| c::Int} <|
                  f :: Int -> Int
                  f x = (a * x + b) * x + c

meaning that the fields should not have global names, only local
names on opening.

Or one could add `methods' to the whole type, being functions
on that type, defined by pattern matching, but with one argument
left of <|

  data Fred = F1 | F2 | F3
    with cycle :: Fred
         F1 <| cycle = F2
         F2 <| cycle = F3
         F3 <| cycle = F1

Again, cycle wouldn't be globally declared.

Goodness me, it's a per-type namespace, but not for `ordinary'
application.

There's a catch, of course. When you write

  r <| e

you give the typechecker no clue as to the type of r: it just
has to infer the type of r and hope it's a datatype. I suggest
this is perfectly sustainable, given that

  (1) your function already has a top-level type signature,
        hasn't it?
  (2) this sort of thing happens all the time with ad-hoc
        polymorphism anyway; when you have

          class Blah x where
            blah :: x -> x

          instance Blah (Maybe Int) where
            blah Nothing = Just 0
            blah (Just x) = Just (x + 1)

        what's

          blah Nothing

        ?

Is this plausible?

Conor


More information about the Haskell mailing list