state of Standard

Johannes Waldmann joe@informatik.uni-leipzig.de
Fri, 14 Mar 2003 14:59:53 +0100 (MET)


Serge, I support your point of view

> A language should support a natural naming of objects.
>   data Operator = 
>        Operator{opName        :: String, ...
>                } 
> is not good -- due to `op' prefix.

You can use qualified names, this solves the problem (to a certain extent)

module Operator where data Operator = Operator { name :: String, ... }
module Foo where import qualified Operator ; foo = Operator.name bar

It is a bit tedious to construct records that way, as in
bar = Operator.Operator { Operator.name = "bar", ... }


there are (at least) two better (?) solutions:

a) something that works "only" for records, 
   for instance one would like to write the above as

   bar = Operator.Operator { name = "bar", ... }

   (I think this has been suggested here before)

   Actually, the above looks a bit silly, so one should write

   module Operator where data Type = New { name :: String }
   module Foo where import qualified Operator
   bar = Operator.New { name = "bar" , .. } :: Operator.Type


b) full static overloading (resolved by looking at the argument types)
      
   of course this is (one more) source of increased complexity
   in the language (affecting the user, and the implementors) 
   (This has been discussed here as well,
   although I don't remember the result. Was there one?)
   

It is sometimes strange to see how Haskell as a language
is so powerful in all its advanced respects (esp. the type/class system)
but is obviously lacking in some others (e. g., naming issues like the above)

On the other hand, this seems to reflect the "academic" origin
of the language (resp., its main body of designers, implementors, and users):
You won't get promoted, or tenured, or whatever,
just for implementing something as (seemingly) simple 
as a module and scoping system - that's not research, "just" engineering.
And indeed, some of the more "engineered" languages
(think of Ada or Java) seem to have got this one right, or at least better.
But we can't blame the academics for doing their job
(i. e. research is what they're paid for). 

Best regards,
-- 
-- Johannes Waldmann ---- http://www.informatik.uni-leipzig.de/~joe/ --
-- joe@informatik.uni-leipzig.de -- phone/fax (+49) 341 9732 204/207 --