Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread John Meacham
what about method and data constructors?

data public: Foo a = private: Bob | public: Baz

class Foo a where
private:
foo :: a
public:
baz :: a


I really like haskell's current module system. A whole lot. other than
the minor tweaks that have been mentioned. A really nice thing is that
it is all about the namespace. unlike other languages, like java where
your namespace is intrinsically linked to your class hierarchy, or C++
where bringing names into scope implies textual inclusion of arbitrary
code, haskell has the wonderful property that the module system is
purely about matching identifiers to their meaning. A side effect of
this is that you can determine what names are in scope purely by by
looking at the export/import lists of your modules and there is never a
need nor a reason to look anywhere else. it is all nice and
self-contained right there at the top of each module. moving to
individual annotations would be a large step backwards IMHO.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Jared Updike
And this

public foldr:: (a -> b -> b) -> b -> [a] -> b
public foldr f z [] =  z
public foldr f z (x:xs) =  f x (foldr f z xs)

or is it

public foldr:: (a -> b -> b) -> b -> [a] -> b
foldr f z [] =  z
foldr f z (x:xs) =  f x (foldr f z xs)

and now things aren't lined up.

  Jared.

On 2/24/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:
> Hello Claus,
>
> Friday, February 24, 2006, 7:53:09 PM, you wrote:
>
> CR> public class C a
> CR> where
> CR> public m1 :: a
> CR> private m2 :: a -> String
>
> please don't stop on this!
>
> public map (private f) (public (private x:public xs)) =
>   private (public f (private x))
>   `public :`
>   private map (public f) (private xs)
>
>
> --
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
>
> ___
> Haskell-prime mailing list
> Haskell-prime@haskell.org
> http://haskell.org/mailman/listinfo/haskell-prime
>


--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Bulat Ziganshin
Hello Claus,

Friday, February 24, 2006, 7:53:09 PM, you wrote:

CR> public class C a
CR> where
CR> public m1 :: a
CR> private m2 :: a -> String

please don't stop on this!

public map (private f) (public (private x:public xs)) =
  private (public f (private x))
  `public :`
  private map (public f) (private xs)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Bulat Ziganshin
Hello Claus,

Friday, February 24, 2006, 6:55:51 PM, you wrote:

CR> not quite (though I believe that would be close to Simon M's idea).

CR> in my modification, both map and length would move completely
CR> into the export section

WHY? it's not the interface. implementation of exported functions is
of no interest for module users like the implementations of any other
functions. i tried to emphasize this moment - in any case we should
either duplicate part of code or have the definitions splitted in the
very unpleasant manner. i prefer instead to not have "interface"
section at all and generate it automatically by haddock

>> -- |iterate function over list
>> map :: (a->b) -> [a] -> [b]
>> 
>> -- |find length of list
>> length :: [a] -> Int
>> 
>> private:
>> 
>> map f (x:xs) = f x : map f xs
>> map f [] = []
>> 
>> length xs = length# xs 0#
>> 
>> length# (x:xs) n# = length# xs (n# +# 1)
>> length# [] n# = n#
>> 
>> 
>> and in order to see map's type or comment when i implement it, i
>> should see to other part of file. i personally prefer to have
>> public/private modifiers on each function and gather interface
>> documentation by tools like haddock
>> 
>> 

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Claus Reinke

> > i personally prefer to have
> > public/private modifiers on each function and gather interface
> > documentation by tools like haddock
> Me too.



having to type one of "public" or "private" at each
function site would get really tedious...


you mean as in "public static void main(String[] args) { ..}"
instead of "main args = .."?-) there are such languages, and
I'm happy to say Haskell isn't one of them! 


also remember that you'd need to add "public" and "private"
to more than just function definitions:

public class C a 
   where

   public m1 :: a
   private m2 :: a -> String

public infixl :@
private infixl :@@ -- internal applications

public data Expr a = public Var a
 | Expr a (public :@)  Expr a
 | Expr a (private :@@) Expr a
deriving (private Show, public Eq)

private data Rec a = public Rec{ private distance :: a
   , public x :: a
   , public y :: a}
   deriving (public Show)

private -- please, no!-)


the nice thing about Haskell syntax is that is is fairly "quiet",
there isn't much that doesn't have to be there or could distract
from the essentials of the code. please, let's keep it that way.

cheers,
claus

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread kahl
Bulat.Ziganshin responded to Claus Reinke:
 > 
 > CR> yes, this would add one constraint on where to place definitions. but
 > CR> grouping logically related definitions together is not quite what one 
 > CR> might think anyway: aren't the definitions making up the interface
 > CR> most strongly related, with the others just changeable auxiliaries?
 > 
 > [...]
 >
 > and in order to see map's type or comment when i implement it, i
 > should see to other part of file. i personally prefer to have
 > public/private modifiers on each function and gather interface
 > documentation by tools like haddock

In my personal experience, I have three kinds of Haskell modules:

 1.  Exporting everything
 2.  Exporting almost everything
 3.  Having a designed export interface


I agree with Claus' comment,
understanding it to refer to modules of kind 3.

I also agree with the motivation of Bulat's comment,
and understand it to refer mostly to modules of kind 1.


I found myself striving to eliminate large modules of kind 2,
typically replacing them by a large module of kind 1
which re-exports a small kernel module of kind 3
(or, to be honest, frequently of kind 2).
This method is mostly for statype encapsulation ---
another motivation to have kind 2 modules are auxiliary functions:
I mostly strive to abstract them away
into (kind 1) standard library supplement modules, or keep them local.

Therefore, I essentially do not have large kind 2 modules,
and for each module of kind 3 (or small module of kind 2) in my code base,
I guess I have at least five of kind 1.
(I.e., for each module with an explicit export list, at least five without,
 or with an export list that only adds re-exports of imports.)


Module kind 1 is of course extremely well-served by the option
not to have an explicit export list ---
I may have overlooked something,
but I did not have the impression that anybody wanted to abolish that,


Module kind 3, where we put real thought into design of the interface,
would of course be served better by a more explicit interface syntax
(like ML's signatures, or module types).


Therefore I would propose that we try to get a better
and more conscious feeling of the different module kinds we need supported,
and then optimise the language for each module kind separately
as far as possible.

Do you have or recognise other frequently-used module kinds?
Should we consider collection modules, or, more generally, kind 1 modules
that also re-export imports, as a separate kind?


Wolfram

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Sebastian Sylvan
On 2/24/06, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> On Friday 24 February 2006 16:38, Bulat Ziganshin wrote:
> > i personally prefer to have
> > public/private modifiers on each function and gather interface
> > documentation by tools like haddock
>
> Me too.
>

Maybe if you only had to specify which functions where public (whereas
private is implied -- or maybe not even allowing it to save a
keyword). But having to type one of "public" or "private" at each
function site would get really tedious...

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Benjamin Franksen
On Friday 24 February 2006 16:38, Bulat Ziganshin wrote:
> i personally prefer to have
> public/private modifiers on each function and gather interface
> documentation by tools like haddock

Me too.

Ben
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Claus Reinke

so:


not quite (though I believe that would be close to Simon M's idea).

in my modification, both map and length would move completely
into the export section, length# would stay in the local section.
both sections would just be module s., containing full
definitions, declarations, imports. to export anything, move it
to the export section, to hide anything, move it to the local 
section (and in case that wasn't clear, these would be two 
sections of the same module , only distinguished by

whether or not their contents are exported).

cheers,
claus


-- |iterate function over list
map :: (a->b) -> [a] -> [b]

-- |find length of list
length :: [a] -> Int

private:

map f (x:xs) = f x : map f xs
map f [] = []

length xs = length# xs 0#

length# (x:xs) n# = length# xs (n# +# 1)
length# [] n# = n#


and in order to see map's type or comment when i implement it, i
should see to other part of file. i personally prefer to have
public/private modifiers on each function and gather interface
documentation by tools like haddock


--
Best regards,
Bulatmailto:[EMAIL PROTECTED]


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Bulat Ziganshin
Hello Claus,

Friday, February 24, 2006, 2:46:40 PM, you wrote:

CR> yes, this would add one constraint on where to place definitions. but
CR> grouping logically related definitions together is not quite what one 
CR> might think anyway: aren't the definitions making up the interface
CR> most strongly related, with the others just changeable auxiliaries?

so:

-- |iterate function over list
map :: (a->b) -> [a] -> [b]

-- |find length of list
length :: [a] -> Int

private:

map f (x:xs) = f x : map f xs
map f [] = []

length xs = length# xs 0#

length# (x:xs) n# = length# xs (n# +# 1)
length# [] n# = n#


and in order to see map's type or comment when i implement it, i
should see to other part of file. i personally prefer to have
public/private modifiers on each function and gather interface
documentation by tools like haddock


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Haskell-prime Digest, Vol 2, Issue 58

2006-02-24 Thread Malcolm Wallace
Axel Simon <[EMAIL PROTECTED]> wrote:

> public:
> private:
> 
> Furthermore, I'd like to propose to have a colon after public,
> private, default, infixl, infixr, infix, which frees all these
> identifiers for normal use as identifiers. There was a mail earlier on
> "Collection Framework" with a complaint that 'default' is a keyword.

Hmm, so how would I construct or pattern-match a list of such things?

f (default:defaults) =  ...

Regards,
Malcolm
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Haskell-prime Digest, Vol 2, Issue 58

2006-02-24 Thread Sebastian Sylvan
On 2/24/06, John Hughes <[EMAIL PROTECTED]> wrote:
> From: "Claus Reinke" <[EMAIL PROTECTED]>
>
> let's go through 5.2 "Export Lists" to see what would be missing
> if we tried to replace the export list with a separation of a module
> into a public (exported) and a private (local) part:
> ...
> any other issues I missed here?
>
> I feel unkeen.
>
> One of the nice things about Haskell is that definitions can appear in any 
> order. That makes it possible to gather a group of logically related 
> definitions together, within a module. With your proposal, exported 
> definitions and non-exported ones would have to be separated.
>
> What would that mean in practice? Suppose I have a few exported functions and 
> a collection of auxiliary functions that are used to implement them. I have 
> two choices: either I put the exported definitions in the public section, and 
> the remaining ones elsewhere in the private section, or I put everything in 
> the private section with appropriate redeclarations in the public part -- 
> exportedName = localExportedName or whatever. The first alternative has the 
> disadvantages that logically related code is separated, and that the public 
> section of the module may itself become quite large (since it contains full 
> function definitions), making it hard to see at a glance what the exported 
> names are. The second alternative has the disadvantage of introducing an 
> indirection---finding the actual definition of an exported function becomes 
> more difficult, because one must both scan the module for it, and first look 
> up the public section to see what the private version is called. Neither 
> alternative feels really attractive to me.
>
> Today's export lists at least have the advantage that it is easy to see what 
> is exported, even if changing the status of a definition from private to 
> public is a little awkward (with edits in two places). With a tool like 
> Haddock installed too, once gets a pretty good view of the 
> interface---arguably better than one can get from a public module section. 
> Perhaps, given that Haddock is available, a public modifier makes more sense 
> than an explicit export list---although code browsing would then require 
> running Haddock during development much more often than today, and 
> potentially on syntactically incorrect or ill-typed modules.
>
> Incidentally, the Erlang equivalent of Haddock, edoc, is distributed with the 
> compiler, so that all Erlang installations include the tool, no matter what 
> platform they're running on. Surely that's a prerequisite for adapting the 
> language design on the assumption that tools of various kinds are available?
>
> John
>
>
>

Just a quick thought. How about having separating the code in two
sections, public and local, BUT allowing you to export local names by
simply mentioning them in the public section. So the equivalent of
what we have now would be to write all your code in the private/local
section, and then put the names of the functions you want exported in
the public section.
These "exported locals" could be in a separate list like it is now (in
addition to the public section) or it could be enough to just put them
in the public top level like so

--
public:
foo = blah + bar

bar -- this re-exports a local bar defined in the private section

A(B,D) -- re-exports data type A with constructors B and D (but keeps C hidden)

baz = blahglah

private:
bar = blahblah
data A = B  | C | D
--

Maybe some keyword to re-export local definitions is a good idea. Like
"export bar" or something...

This means you can still group locally related functions together, but
you're allowed to write defintions in the public part of the module as
well. So you get all your public stuff in the same place (good), while
the definitions for some of those items may be in the local area if
that makes sense (good). And there's no extra indirection since the
public name isn't different from the priveate one (good). You do have
to type the name twice, but that's no different from what we have now
(and better, since it's "pay as you go" - you only need to retype
names if you choose to put the definition in the local part).

A likely coding practice would be to put short and simply defitions in
the public interface, but using the exporting feature for larger
functions (which need a significant amount of local helper functions
etc.).

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Claus Reinke

I feel unkeen.


you will notice that I haven't actually proposed adopting this (yet:-);
neither did Simon M for his original version. so far, I had thought
Haskell's export/import language quite limited, but useable and simple.
so apart from fixing the asymmetries between export and import, and
adding a few missing features, I wasn't expecting much change.

So, I was surprised to see that following the route of sections and
dropping export lists altogether might actually simplify the language and
accomodate other proposed variations more easily than the current
system. it isn't often that we find such opportunities in language design.

yes, this would add one constraint on where to place definitions. but
grouping logically related definitions together is not quite what one 
might think anyway: aren't the definitions making up the interface

most strongly related, with the others just changeable auxiliaries?
and how do you flatten the graph of mutually related (according to
one of many possible criteria) definitions, without separating some
of them? even refactoring does not solve this - you can't rewrite
your code (even automatically) any time you want to take a different
view on your sources. 


in other words, you can only _partially_ support _one_ of many
relations by actual proximity. everything beyond falls firmly into
tool support for virtual proximity (creating useful views of your
sources on the fly, without changing the sources, as needed).

for instance, I really dislike the public/private modifier idea
because it splatters logically related items from the export interface
and the definition of said interface all over the source code, so I 
need a tool to gather the interface definition back together;-)


even with the current system, I constantly need tool support
to keep one auxiliary view on the module header while editing 
its body, and another auxiliary view on the definitions of any
imported items I might be using. and though I always start with 
related definitions close together, it usually doesn't take long 
before that fails for some reason or other (not to mention that 
my view of what should be related changes all the time 
depending on what I'm doing).


the other problem you mention is that either the export section
would contain code (rather than just names) or synonym definitions
(rather than just names). that is true, and I don't particularly like
this (especially the second bit), but I can't see yet to what extent 
that problem would bite in practice. code navigation should 
certainly not be an issue here (even the ageing vim supports tag

stacks, and ghc head has supported tag file generation for some
time now; hmm, that reminds me that we should have hugs-style
editor integration in ghci..).

as for Haddock, it seems to have won the fight for the documentation
niche, so it would be nice to have it available with every Haskell
installation. but generally, the availability of a specific tool is not a
prerequisite for aiming for a balance between language and tool
design. you just need committment to building/distributing and
maintaining some tool to cover the issue (e.g., both ghci and hugs
support the :browse  command, which is about the
easiest way to extract the interface; and that has been used in
at least one editor mode, without needing Haddock).

what is a prerequisite is that the language definition does not
ignore tools, and that -apart from balancing the responsibilities
of language and tools- the definition provides foundations on
which tool building would be supported more easily than today.

cheers,
claus

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


export modifiers, was: Re: Haskell-prime Digest, Vol 2, Issue 58

2006-02-24 Thread Johannes Waldmann
Axel Simon wrote:

>> One of the nice things about Haskell is that definitions can appear in any 
>> order. That makes it possible to gather a group of logically related 
>> definitions together, within a module. With your proposal, exported 
>> definitions and non-exported ones would have to be separated.
> 
> ... what about a Jave/C++ like approach 

This has been suggested by some,
and John Hughes did in fact support this later in his email:

> Perhaps, given that Haddock is available, a public modifier makes more
> sense than an explicit export list-

and I'd like to underline that this modifier should be attached
to a declaration individually (as in Java),
and *not* start a region (similar to C++)

> public:
> 
> main = 
> 
> private:
> 
> helper1 = ...
> helper2 = ...
> 
> public:

because this would introduce order dependencies again:
you'd have to search up the source code file
to find out whether a declaration is private or not,
and you'd have to be careful when moving around code.

Respectfully submitted,
-- 
-- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 --
 http://www.imn.htwk-leipzig.de/~waldmann/ ---

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Haskell-prime Digest, Vol 2, Issue 58

2006-02-24 Thread Axel Simon
On Fri, 2006-02-24 at 11:20 +0100, John Hughes wrote:
> From: "Claus Reinke" <[EMAIL PROTECTED]>
> 
> let's go through 5.2 "Export Lists" to see what would be missing
> if we tried to replace the export list with a separation of a module
> into a public (exported) and a private (local) part:
> ...
> any other issues I missed here?
> 
> I feel unkeen.
> 
> One of the nice things about Haskell is that definitions can appear in any 
> order. That makes it possible to gather a group of logically related 
> definitions together, within a module. With your proposal, exported 
> definitions and non-exported ones would have to be separated.

I agree, I'd find it inconvenient, too. But what about a Jave/C++ like
approach where you sprinkle public and private declarations throughout?
E.g.

public:

main = 

private:

helper1 = ...
helper2 = ...

public:

...

In particular you can have

public: A(C,D)

data A = A | B | C | D

which only exports the C and D constructors.

Furthermore, I'd like to propose to have a colon after public, private,
default, infixl, infixr, infix, which frees all these identifiers for
normal use as identifiers. There was a mail earlier on "Collection
Framework" with a complaint that 'default' is a keyword.

Axel.

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Haskell-prime Digest, Vol 2, Issue 58

2006-02-24 Thread John Hughes

   From: "Claus Reinke" <[EMAIL PROTECTED]>

   let's go through 5.2 "Export Lists" to see what would be missing
   if we tried to replace the export list with a separation of a module
   into a public (exported) and a private (local) part:
   ...
   any other issues I missed here?

I feel unkeen.

One of the nice things about Haskell is that definitions can appear in any 
order. That makes it possible to gather a group of logically related 
definitions together, within a module. With your proposal, exported definitions 
and non-exported ones would have to be separated.

What would that mean in practice? Suppose I have a few exported functions and a 
collection of auxiliary functions that are used to implement them. I have two 
choices: either I put the exported definitions in the public section, and the 
remaining ones elsewhere in the private section, or I put everything in the 
private section with appropriate redeclarations in the public part -- 
exportedName = localExportedName or whatever. The first alternative has the 
disadvantages that logically related code is separated, and that the public 
section of the module may itself become quite large (since it contains full 
function definitions), making it hard to see at a glance what the exported 
names are. The second alternative has the disadvantage of introducing an 
indirection---finding the actual definition of an exported function becomes 
more difficult, because one must both scan the module for it, and first look up 
the public section to see what the private version is called. Neither 
alternative feels really attractive to me.

Today's export lists at least have the advantage that it is easy to see what is 
exported, even if changing the status of a definition from private to public is 
a little awkward (with edits in two places). With a tool like Haddock installed 
too, once gets a pretty good view of the interface---arguably better than one 
can get from a public module section. Perhaps, given that Haddock is available, 
a public modifier makes more sense than an explicit export list---although code 
browsing would then require running Haddock during development much more often 
than today, and potentially on syntactically incorrect or ill-typed modules.

Incidentally, the Erlang equivalent of Haddock, edoc, is distributed with the 
compiler, so that all Erlang installations include the tool, no matter what 
platform they're running on. Surely that's a prerequisite for adapting the 
language design on the assumption that tools of various kinds are available?

John



___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime