[Haskell-cafe] Avoiding name collisions by using value spaces
instead of modules
Brian Hulley
brianh at metamilk.com
Sun Jan 8 12:47:19 EST 2006
----- Original Message -----
From: "Daniel Fischer" <daniel.is.fischer at web.de>
To: "Brian Hulley" <brianh at metamilk.com>
Cc: "Haskell-cafe" <haskell-cafe at haskell.org>
Sent: Sunday, January 08, 2006 3:47 PM
Subject: Re: [Haskell-cafe] Avoiding name collisions by using value spaces
instead of modules
> Am Sonntag, 8. Januar 2006 14:06 schrieb Brian Hulley:
>> Hi -
>> A main problem I've found with Haskell is that within a module, too many
>> things are put into the same scope. For example
>>
>> data Tree a b = Leaf a | Node {elem::b, lhs::Tree a b, rhs::Tree a b}
>>
>> < snip>
>> I propose that the above declaration should introduce a *new module*
>> Tree,
>> as a sub module of the containing module, and Leaf, Node, elem etc will
>> be
>> put into this module, and not the module containing the data declaration
>> itself.
>
> What speaks against putting the data declaration in a separate module:
>
> module ThisKindOfTrees where
>
> data Tree a b = ...
>
> and then use qualified imports (with a short alias), if you want to use
> different kinds of trees in one module?
All I'm proposing is that the compiler should do all this painful work for
you, so that you don't need to bother creating a different file that then
needs two import directives to achieve the effect I want. Is there any case
where you would *not* want a type to be declared in its own module?
> Yes, more files, but, IMHO, much more readable.
In what way is it more readable?
>> <snip>
>> For example, for
>>
>> module M where
>> foo :: forall b. Eq a => Set (Tree a) -> Tree ([a],b) -> [Tree (a,b)]
>>
>> we ignore the forall and Eq, and replace tyvars and tuple the results to
>> get:
>>
>> M.(Set (Tree ?), Tree ( (,) ( [] ?) ?), [] (Tree ( (,) ? ?))).foo
>>
>> as the fully qualified reference to the entity we've just declared.
>
> Looks absolutely horrible to me. What would we gain?
> We could have
>
> M.(Set (Tree ?), Tree ( (,) ( [] ?) ?), [] (Tree ( (,) ? ?))).foo
> and
> M.(Int, Set (Tree ?), Tree ( (,) ( [] ?) ?), [] (Tree ( (,) ? ?))).foo
>
> but why? Do we really want it? I certainly don't.
I agree that I would certainly not want to have to write out the fully
qualified name (or superfluously qualified name as you point out with
Int,...), but I think we would gain a great deal from this, because just by
making a declaration in module M, we've effectively created an infinite
number of child modules that the declaration belongs to, without having to
create an infinite number of files and write an infinite number of import
directives in M.
For example, suppose I'm writing a module M that deals with grammar, where
the elements in a grammar rule are parameterised so that rules can be
written using strings but processed as if we'd used ints instead:
data Element a = Terminal a | Nonterminal a | Action a
data Rule a = Rule (Element a) [[Element a]]
Now I want to convert elements and rules from a to Int, so at the moment I
have to write:
convertElement :: Element a -> CM (Element Int)
...
convertRule :: Rule a -> CM (Rule Int)
for some appropriate monad CM.
Whereas I would have much preferred to use just the word "convert" in both
cases. It is tremendously annoying to have to suffix everything with the
type name.
In another situation, suppose we have two types T1 and T2, and some function
convert :: T1 -> T2
The problem I have is which module (if I used a separate module for T1 and
T2), should I put the convert function in? Essentially I think it belongs to
the space of relations between T1 and T2, hence my idea to use tuple
notation to get a module called (Q1,Q2) eg (Set,Map). But I certainly don't
want the bother of having to create a new file and type import directives
into M every time I want to define a function on some different relation
space.
Really I don't want to have to think about modules at all, since I'd like to
write code that organises itself into modules (using these ty-tuples and
top-down type/identifier-resolution inference) so I can concentrate on typed
values and relations between them without all the module-level plumbing.
>> <snip>
> you'd havoc because sometimes you've just made an error -- which wouldn't
> then be spotted by the type-checker.
I agree this could be a disadvantage - ease of coding is gained but some
kinds of errors cannot be caught so easily.
>>
>> Finally (apologies for this long post), returning to the use of ^ to
>> allow
>> an object oriented way of thinking consider:
>>
>> insert :: a -> Set a -> Set a
>> ps = singleton 3
>> qs = insert 4 ps
>> rs = ps^insert 4
>>
>> When resolving "insert" used in the binding for rs, the compiler should
>> see
>> that we are looking for some function Set Int -> Int -> Set Int, and
>> hence
>> will be looking in the current module augmented by the Set module.
>> However
>> the Set module only has a binding for insert with type a -> Set a -> Set
>> a.
>> So the compiler should generate a new function insert' from insert by
>> moving the first Set a arg to the front.
>
> Automatic permutation of arguments? Has its merits, but goodbye to
> type-safety, I believe.
Yes, perhaps this does make life too complicated.
>> <snip>
>> things I think are wrong with Haskell such as the way the current layout
>> rule allows one to write code that would break if you replaced an
>> identifier with one that had a different number of characters in it etc),
>
> So you would have to adjust your indentation in that case.
Surely that is most terrible! :-)
> If you consider that a serious problem, what about using braces and
> semicolons? If you do it like
>
> foo bar = do { x <- something bar
> ; more x
> ; yetMore x bar
> }
>
> you get the advantages of both, layout-enhanced readability and
> layout-insensitivity due to explicit braces and semicolons.
It is quite simple to create a new layout rule. My idea with this is that
all lines should start with zero or more tab characters (non-tab leading
whitespace is disallowed), and all layout blocks should start on a new line.
Moreover, it is possible to completely dump the ugly let..in construct, and
make "=" one of the tokens that can start a new layout block, so instead of:
f x = let a = x+1
b = x + 2
in a + b
one would simply write:
f x =
a = x+1
b = x+2
a + b
This allows you to use a variable width font and does not break when the
identifiers are renamed. Also, I would use ',' instead of ';' in an explicit
block, so that {,} becomes a general construct that can be used for records
as well as blocks (so you can use layout for records too), and, while I'm on
the subject of things to change, I would use {,} for predicates instead of
(...)=> and use => (or =) instead of -> in the value syntax:
data (Eq a, Ord a) => Set a ... -- looks like a tuple but has
nothing to do with tuples
data {Eq a, Ord a} Set a -- looks more like a set of predicates
this way
case p of [] => q \x y => x+y (avoids all the problems
when you want to type things)
<Rearranged>
>'^' is definitely a bad choice, 'cause it's exponentiation (and has a long
>and
> venerable history as symbol therefore).
:: would mean list cons, as it has been since the birth of ML
: would be used for type annotations as it has been since the birth of
Pascal (at least)
o would be used for function composition so that . can be used for
qualification
user defined fixities would be discarded because they make code
unreadable by anyone else
>
>> so any feedback on these ideas would be welcome.
>
> You want object-oriented Haskell?
> Go ahead (there's something around already)
I think this value space idea is far more powerful than just object
orientation, because in OOP, functions can only be associated with their
first argument, whereas with value spaces, values are associated with the
whole space of relations (ie all args + return value) they are concerned
with.
> but make it a language of its own.
> No offence intended, but I like Haskell as it is and haven't really seen
> the
> merits of OO-overloading yet.
Fair enough. I hope it was ok to post these ideas to this group because
Haskell is very similar to the language I'm trying to create and it is very
useful to get this feedback. I'm happy if anyone wants to incorporate any of
my ideas above into Haskell but equally happy if they don't :-)
Best regards,
Brian Hulley.
More information about the Haskell-Cafe
mailing list