Keep the present Haskell record system!

Johannes Waldmann waldmann at imn.htwk-leipzig.de
Tue Mar 7 03:03:44 EST 2006


Cale Gibbard wrote: (a thoughtful response, thank you) and ...

> ... field labels can be renamed such that they don't overlap.
> Inventing new names is not hard work. 

Oh yes it is. I want meaningful names, and if the meaning of two things
is identical, then inventing separate names is hard and unnecessary
and misleading.

> (You can just put part or all of the type name in the labels, 

Ugly ugly ugly. By writing fooBar (for "the foo of Bar")
I'm putting type or module information in a name.
That's a bad idea because it bypasses the type or module system.


I think I really want a separate component namespace per type,
and I can only get this by putting each type in its own module,
but then another problem comes up: how to name the module/the type?

You see this in e. g. Data.Map: it contains the type Map, and says
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html

> This module is intended to be imported qualified, to avoid name
> clashes with Prelude functions. eg.  import Data.Map as Map

but then what is the type of a map? It's Data.Map.Map (or, as the
documentation suggests, Map.Map, which does not look any better).

Sometimes my conclusion is "module Foo where data Type = Make { ... }"
because then "import qualified Foo ; x :: Foo.Type = Foo.Make ..."
(in case I'll publish the constructor). You see I want to avoid
inventing a name for the type and its constructor (if there is only one)
because I already have done it (it's the module name).

So .. what if we just allow to write a data (or class?) declaration
directly (instead of a module declaration). E. g. the file "Foo.hs"
contains "data Foo where (... constructors as in GADT ...) ;
some_function :: ..." with the effect that after "import qualified Foo"
from elsewhere we can write "x :: Foo; .. Foo.some_function ..."
Just an idea.


PS: GADTs are way cool! Any chance of having them in Haskell-Prime?
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
---- http://www.imn.htwk-leipzig.de/~waldmann/ -------



More information about the Haskell-prime mailing list