Tomasz Zielonka wrote:
[A bit late reply - I've just returned from vacation]

On Sun, Jan 08, 2006 at 05:47:19PM -0000, Brian Hulley wrote:
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?

I can think of such cases - for example consider a set of mutually
recursive datatypes used to represent abstract syntax trees in some
language. Of course, I imagine that "your modules" could be introduced
in such a way that would still allow recursion, but it's simply more
natural for me to place all those declarations in one module named
Syntax or AST.

My idea was that modules would be hierarchical, so that for example you could have a module AST as follows:

module AST where

   data Data1 = ...
   data Data2 = ...

This would be equivalent to writing something like:

module AST where                    -- in file prefixPath/AST.hs
import AST.Data1 as Data1 (Data1) -- using partially qualified module names (not yet supported AFAIK?)
   import AST.Data2 as Data2 (Data2)

module Data1 where                -- in file prefixPath/AST/Data1.hs
   data Data1 = ...

module Data2 where
   data Data2 = ...

If the fully qualified name of the AST module was prefixSeq.AST then the fully qualified names of the DataN modules would be prefixSeq.AST.DataN

In other words, one file could contain a tree of modules without having to physically put each module into files arranged as a tree on disk with import directives.

An advantage of this would be that you'd no longer need to think up different field names for each record that you use to keep track of state when traversing a data structure - something that quickly becomes extremely difficult as things are at the moment for large modules.


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),

All lines start with at least zero tab characters, trivially.

I could also have said, all characters in leading whitespace must be tabs.


and all layout blocks should start on a new line.

That's a good coding practice

Thanks - glad to see someone agrees with me! :-)

(yes, you can write like this in Haskell
already), making your code more change-friendly, which is especially
important when you use some version control tool. It would be nice if
this could be enforced by the compiler, at least as some kind of a
warning. I encourage you to add such option to some Haskell compiler,
or a coding policy checking tool :-)

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

How about

   f x =
       let
           a = x + 1
           b = x + 2
       in
           a + b

This is how I indent let..in at the moment. However I feel that "let" and "in" just takes up space, and while useful in describing the abstract syntax, I don't see what use it has in the concrete syntax of a language, apart from the fact that in the current layout rule, "let" is needed to introduce a block. I think that because "let" and "in" are rather redundant, people like to squash them into the same lines as non-redundant code, leading to:

   f x = let a = x + 1
                b = x+2
           in a+ b

or a million times worse:

f x = let a = a+1 ; b = x+2 -- mixing up two different ways of writing a block of things
                c = a + b
           in c


Anyway, I would use "where" here.

I agree this would be neater in this case - sometimes let..in is still needed eg in a branch of an if construct etc.


one would simply write:

   f x =
           a = x+1
           b = x+2
           a + b

I don't like it. It's shorter, but less readable too.

Yet this is very similar to how you write functions in C++, C, Java, C# etc so for anyone used to these languages, it seems very natural ie

   f(x) {
       a = x+1;        // Hurray! no need to write "let" :-)))
       b = x+2;        // ((single assignment simulating binding))
       return a+b;
   }

You could simply
write:

  f x =
          a + b
       where
          a = x+1
          b = x+2

or even

   f x = a + b where
       a = x+1
       b = x+2

Regards,
Brian.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to