RE: Heirarchical name space allocation

On Tuesday 30 Mar 2004 10:19 am, Simon Marlow wrote:
The idea is that community self-organisation replaces strict central registration of library names. I think this is an improvement, but perhaps it's a cop out. What do others think?
I think there should be some concensus about the overall structure of the hierarchy, and that should be documented somewhere (so developers don't go and reinvent their own slightly different names for concepts which are already covered). Perhaps it would suffice to just do this for the top level classifications.
In my case I have a pretty complete binding to SDL which I was thinking of tidying up and releasing for other Haskellers. I call it HSDL :-)
But should it go in the Graphics Heirarchy, if so where? Graphics.HSDL? SDL also covers other functionality (like audio) so I was thinking of calling it Multimedia.HSDL, but at present there's no Multimedia top level AFAIK (but then how would I know anyway?). Perhaps someone's already using Multi_Media instead? Or maybe my binding isn't necessarily unique, so perhaps Multimedia.SDL.HSDL? SDL also has quite few bolt on extras too which other people might write bindings for.
There's a kind of "design document" for the hierarchy, which is currently in CVS: fptools/libraries/doc/lib-hierarchy.html. It's also here: http://www.haskell.org/~simonmar/lib-hierarchy.html As we agree on locations for libraries on this list, I've been putting them in the document. Not all the libraries exist yet - this is just a place to put the design of the hierarchy. Multimedia.SDL sounds ok to me. Cheers, Simon

On Wednesday 31 Mar 2004 9:24 am, Simon Marlow wrote:
There's a kind of "design document" for the hierarchy, which is currently in CVS: fptools/libraries/doc/lib-hierarchy.html. It's also here:
http://www.haskell.org/~simonmar/lib-hierarchy.html
As we agree on locations for libraries on this list, I've been putting them in the document. Not all the libraries exist yet - this is just a place to put the design of the hierarchy.
Interesting, no FreeType I see :-( Does the Data.Trees.AVL code exist yet? If not I could donate my implementation. I put quite a bit of effort into producing what I believe should be a fairly fast implemenation.
Multimedia.SDL sounds ok to me.
Maybe if we call what I've produced Multimedia.SDL.Core, though since it actually includes SDL_image and SDL_ttf also, maybe I should split these out to produce.. Multimedia.SDL.Core Multimedia.SDL.Image Multimedia.SDL.TTF so anybody who felt inclined to write a binding for one of the many SDL extension libraries could use Multimedia.SDL.<whatever> (Or maybe my "Core" binding should still be just Multimedia.SDL?) Regards -- Adrian Hey

Adrian Hey wrote:
Does the Data.Trees.AVL code exist yet? If not I could donate my implementation. I put quite a bit of effort into producing what I believe should be a fairly fast implemenation.
The Tree, Seq, Set, Bag and Map stuff should be designed uniformly and therefore be laid into a single hand, i.e. JP Bernardy?, at least initially. Rather than enforcing uniformity by a collection class (as proposed elsewhere), I would like uniformity at the module level wrt. exported functions and types. The hierarchy should allow for several different implemenations of one type with (almost) the same module interface. The current problem is agreeing on interfaces, while there exist quite a few implementations (from which we can pick all the good ones). We should consider your code and (let you) adapt it to an (yet unknown) interface in order to easy performance measures. Christian

On Wed, Mar 31, 2004 at 03:15:32PM +0200, Christian Maeder wrote:
Adrian Hey wrote:
Does the Data.Trees.AVL code exist yet? If not I could donate my implementation. I put quite a bit of effort into producing what I believe should be a fairly fast implemenation.
The Tree, Seq, Set, Bag and Map stuff should be designed uniformly and therefore be laid into a single hand, i.e. JP Bernardy?, at least initially.
Rather than enforcing uniformity by a collection class (as proposed elsewhere), I would like uniformity at the module level wrt. exported functions and types. The hierarchy should allow for several different implemenations of one type with (almost) the same module interface.
I'd like to suggest (again) treating sequences differently from the rest, and that they should be defined by a class: * the class fits within Haskell 98, because sequences have only one parameter, and it's unconstrained. * polymorphism is likely to be more useful with sequences because of the wide range of implementations suited to different purposes. * polymorphism lets you do general adaptors, like Edison's SizedSeq (adding a size) and RevSeq (presenting a reversed view). Also the sequence part of DData is more tentative, but this is the most developed part of Edison. But I'm not suggesting following Edison's interface (classes + uniform exports).

Ross Paterson wrote:
I'd like to suggest (again) treating sequences differently from the rest, and that they should be defined by a class: * the class fits within Haskell 98, because sequences have only one parameter, and it's unconstrained. * polymorphism is likely to be more useful with sequences because of the wide range of implementations suited to different purposes. * polymorphism lets you do general adaptors, like Edison's SizedSeq (adding a size) and RevSeq (presenting a reversed view).
I admit, that supplying further modules for SizedSeq and RevSeq would involve some code duplication. (If several implementations of sequences are used simultaneously qualification is required.) But maybe you could elaborate the advantages of a class that you suggest in more detail. For generic algorithms with sequences, I would suspect smaller classes, e.g. like Monoid, to be more appropriate. Christian P.S. where can I download the actual code of edison? http://www.haskell.org/ghc/docs/edison/

On Wed, Mar 31, 2004 at 04:42:29PM +0200, Christian Maeder wrote:
Ross Paterson wrote:
I'd like to suggest (again) treating sequences differently from the rest, and that they should be defined by a class: * the class fits within Haskell 98, because sequences have only one parameter, and it's unconstrained. * polymorphism is likely to be more useful with sequences because of the wide range of implementations suited to different purposes. * polymorphism lets you do general adaptors, like Edison's SizedSeq (adding a size) and RevSeq (presenting a reversed view).
I admit, that supplying further modules for SizedSeq and RevSeq would involve some code duplication. (If several implementations of sequences are used simultaneously qualification is required.)
Just defining a standard set of operations (filter, dropWhile, etc, etc) will involve lots of duplication. Most of these will involve converting to lists, doing the list thing and converting back. But in a class you supply a default definition.
But maybe you could elaborate the advantages of a class that you suggest in more detail. For generic algorithms with sequences, I would suspect smaller classes, e.g. like Monoid, to be more appropriate.
All the usual advantages of abstraction. I thought SizedSeq was pretty compelling: data Sized s a = N !Int (s a) instance Sequence s => Sequence (Sized s) where ... One instance gets you N new sequences. Monoid isn't quite enough (no way to add elements, for one thing).
where can I download the actual code of edison? http://www.haskell.org/ghc/docs/edison/
The original is in the fptools CVS repository at hslibs/data/edison and also in a GHC source tarball. There's a slightly changed version at :pserver:anonymous@cvs.hfl.sourceforge.net:/cvsroot/hfl

Ross Paterson wrote:
All the usual advantages of abstraction. I thought SizedSeq was pretty compelling:
data Sized s a = N !Int (s a) instance Sequence s => Sequence (Sized s) where ...
One instance gets you N new sequences.
The disadvantage for the user is that for a "Sized Seq" also "Seq" will be in scope and changing the implementation either requires to rename types, to use clever type synonyms, or to use the "Sequence" class constraint. However, I would not mind such a class if it eases other implementions, but from a user's point of view, I want different modules with the same interface (and as few as possible class constraints). "data Sized" is of course generally useful (not only for Sequence) and may be accompanied by a couple of wrap and unwrap functions for certain function profiles to be lifted. Christian

On Thu, Apr 01, 2004 at 01:00:59PM +0200, Christian Maeder wrote:
However, I would not mind such a class if it eases other implementions, but from a user's point of view, I want different modules with the same interface (and as few as possible class constraints).
Do you feel the same way about monads? If not, what's the difference?

Ross Paterson wrote:
On Thu, Apr 01, 2004 at 01:00:59PM +0200, Christian Maeder wrote:
However, I would not mind such a class if it eases other implementions, but from a user's point of view, I want different modules with the same interface (and as few as possible class constraints).
Which "same way"? I'm happy with small and useful classes. Modules better support encapsulation (information hiding), classes allow for overloading of names. You should ask me, how I feel about the Num class, but maybe even this class is not well suited as comparison with the big "Sequence" class. Christian

On Thu, Apr 01, 2004 at 03:41:22PM +0200, Christian Maeder wrote:
Ross Paterson wrote:
On Thu, Apr 01, 2004 at 01:00:59PM +0200, Christian Maeder wrote:
However, I would not mind such a class if it eases other implementions, but from a user's point of view, I want different modules with the same interface (and as few as possible class constraints).
Which "same way"? I'm happy with small and useful classes.
Perhaps the problem is that the classes proposed so far for sequences and other collections have been rather heavy-weight things with a lot of members. Maybe if there were an interface that resisted the temptation to throw everything into the class you would be happier?
You should ask me, how I feel about the Num class, but maybe even this class is not well suited as comparison with the big "Sequence" class.
So how do you feel about the Num heirarchy? Peace, Dylan

Dylan Thurston wrote:
Perhaps the problem is that the classes proposed so far for sequences and other collections have been rather heavy-weight things with a lot of members. Maybe if there were an interface that resisted the temptation to throw everything into the class you would be happier?
Yes maybe
So how do you feel about the Num heirarchy?
It is probably the best possible solution if you use (various) ints and reals simultaneously. But sometimes the class(es) (and defaulting) bites you (if you are a beginner). In 90 percent of the cases I would be happy with Int only (and would be unhappy without overloading for the remaining 10 percent). Christian

On Thu, Apr 01, 2004 at 04:27:56PM -0500, Dylan Thurston wrote:
On Thu, Apr 01, 2004 at 03:41:22PM +0200, Christian Maeder wrote:
Ross Paterson wrote:
On Thu, Apr 01, 2004 at 01:00:59PM +0200, Christian Maeder wrote:
However, I would not mind such a class if it eases other implementions, but from a user's point of view, I want different modules with the same interface (and as few as possible class constraints).
Which "same way"? I'm happy with small and useful classes.
Perhaps the problem is that the classes proposed so far for sequences and other collections have been rather heavy-weight things with a lot of members. Maybe if there were an interface that resisted the temptation to throw everything into the class you would be happier?
Let's consider only sequences, since the others require constraints on the values stored, multi-parameter type classes and functional dependencies. (We're talking about the design of a data structures library we can start to use soon, which rules out such fancy classes, at least in the core interface.) A sequence class would probably have at least 30 methods, since many operations have efficient specializations in at least one implementation. But almost all of these would have default definitions, so new instances could be defined economically. Many operations parameterized on sequences could be defined outside the class. Given that, I don't see why the size of the class is a problem. In particular I don't see why a large common interface is better handled by trying to use the module system to do overloading. That approach certainly leads to a lot of duplicated code (the default definitions and the parameterized functions, e.g. N copies of sum = reduce (+) 0). This is what classes are good for.

Ross Paterson wrote:
Let's consider only sequences, since the others require constraints on the values stored, multi-parameter type classes and functional dependencies. (We're talking about the design of a data structures library we can start to use soon, which rules out such fancy classes, at least in the core interface.)
ok.
A sequence class would probably have at least 30 methods, since many operations have efficient specializations in at least one implementation.
How much existing code would break, if all our current list functions (from Prelude and List) would get the additional context "Sequence" (given we wanted to keep the current names)?
But almost all of these would have default definitions, so new instances could be defined economically. Many operations parameterized on sequences could be defined outside the class.
This somehow splits the interface into some class members and other functions.
Given that, I don't see why the size of the class is a problem. In particular I don't see why a large common interface is better handled by trying to use the module system to do overloading.
I don't want to do overloading with modules, just pick a single (most appropriate) list implementation for my current task.
That approach certainly leads to a lot of duplicated code (the default definitions and the parameterized functions, e.g. N copies of sum = reduce (+) 0). This is what classes are good for.
How many implemenations to you want? Eventually I suspect about 3 implemenations to be useful. I don't know if the size of a class matters, but some code duplication could be avoided by a minimal class (empty, isEmpty, cons, head, tail) as well. Christian

On Fri, 2 Apr 2004, Christian Maeder wrote:
How many implemenations to you want? Eventually I suspect about 3 implemenations to be useful.
Dessy currently has (and none of them is useless): Streams (the only possible lazy implementation) Real-time Queues Deques Write-only Sequences (like the OrdList) Democratic Sequences (the default)
I don't know if the size of a class matters, but some code duplication could be avoided by a minimal class (empty, isEmpty, cons, head, tail) as well.
With these primitives you would just mimick the concrete [] data type, making efficient implementations of almost all other functions impossible. As I argue in http://www.stud.tu-ilmenau.de/~robertw/dessy/fun/democratic/ a "core" consisting of (concat front back) efficiently implemented (i.e. logN each) will permit every other function to be implemented in O(logN). However, most implementations will also provide constant-time (is_empty size first last), and some implementations will also provide constant-time (add_first add_last but_first but_last). Furthermore we need of course 'fold', but also many implementations can implement (apply filter) faster (albeit only by a constant factor) than the default implementation: apply f = fold empty (single . f) (<+>) filter p = fold empty (\x -> if p x then single x else empty) (<+>) Thus, a minimal class will not be small. But I already explained last time, that this is really no problem. Robert

On Thu, 1 Apr 2004, Christian Maeder wrote:
Modules better support encapsulation (information hiding), classes allow for overloading of names.
The old prejudice again... Modules only hide names. Real information hiding requires specifications (or contracts, or refinement, or whatever you call them). You can do that with modules or with classes. I think classes are better, the proposed Abstract Collections do it with classes, this works fine. Nobody yet did it with modules... Robert

Ross Paterson wrote:
Do you feel the same way about monads? If not, what's the difference?
Is this Ross? Or has the famous Eliza program hijacked his email address? (Sorry, couldn't resist... :-) Cheers, S. P.S.: For the younger amongst us: Google for "Eliza" and "Weizenbaum".

On Thu, Apr 01, 2004 at 03:59:01PM +0200, Sven Panne wrote:
Ross Paterson wrote:
Do you feel the same way about monads? If not, what's the difference?
Is this Ross? Or has the famous Eliza program hijacked his email address?
Tell me more about Eliza.

At 16:10 01/04/04 +0100, Ross Paterson wrote:
Tell me more about Eliza.
:-) Ah, the date, the date! #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Thu, 1 Apr 2004, Christian Maeder wrote:
"data Sized" is of course generally useful (not only for Sequence) and may be accompanied by a couple of wrap and unwrap functions for certain function profiles to be lifted.
Yeah, just what Dessy does with its Cached and OCached meta-types (i.e. kind (* -> *) -> (* -> *)). Robert

On Wednesday 31 Mar 2004 2:15 pm, Christian Maeder wrote:
Adrian Hey wrote:
Does the Data.Trees.AVL code exist yet? If not I could donate my implementation. I put quite a bit of effort into producing what I believe should be a fairly fast implemenation.
The Tree, Seq, Set, Bag and Map stuff should be designed uniformly and therefore be laid into a single hand, i.e. JP Bernardy?, at least initially.
Rather than enforcing uniformity by a collection class (as proposed elsewhere), I would like uniformity at the module level wrt. exported functions and types. The hierarchy should allow for several different implemenations of one type with (almost) the same module interface.
The current problem is agreeing on interfaces, while there exist quite a few implementations (from which we can pick all the good ones).
We should consider your code and (let you) adapt it to an (yet unknown) interface in order to easy performance measures.
If I've understood you, I have to say I'm sceptical about this. IMO the API exported by Data.Trees.AVL should be the raw AVL tree (only) API, designed exclusively for the convenience of AVL tree users and should not be constrained by other considerations. I can see no good reason why the the API of Data.Trees.AVL should bear any resemblance to that of Data.Trees.RedBlack or any other kind of tree or container. It's perfectly reasonable that thay should be different because they facilitate different operations with varying degrees of efficiency (or maybe not at all). If folk have chosen AVL trees in preference to RedBlack trees or vice-versa they have presumably done so for a good reason. If folk also want find some common ground for all container types and make generic container classes or whatever, and want to make instances of those classes from AVL trees, that's fine too. But this should be done elsewhere in the hierarchy I think, or maybe included as a supplement to (but not a substitute for) the raw API. Regards -- Adrian Hey

Adrian Hey wrote:
If I've understood you, I have to say I'm sceptical about this. IMO the API exported by Data.Trees.AVL should be the raw AVL tree (only) API, designed exclusively for the convenience of AVL tree users and should not be constrained by other considerations.
I can see no good reason why the the API of Data.Trees.AVL should bear any resemblance to that of Data.Trees.RedBlack or any other kind of tree or container. It's perfectly reasonable that thay should be different because they facilitate different operations with varying degrees of efficiency (or maybe not at all). If folk have chosen AVL trees in preference to RedBlack trees or vice-versa they have presumably done so for a good reason.
I thought, the common denominator (i.e. interface) are binary search trees. Christian

On Friday 02 Apr 2004 10:18 am, Christian Maeder wrote:
Adrian Hey wrote:
If I've understood you, I have to say I'm sceptical about this. IMO the API exported by Data.Trees.AVL should be the raw AVL tree (only) API, designed exclusively for the convenience of AVL tree users and should not be constrained by other considerations.
I can see no good reason why the the API of Data.Trees.AVL should bear any resemblance to that of Data.Trees.RedBlack or any other kind of tree or container. It's perfectly reasonable that thay should be different because they facilitate different operations with varying degrees of efficiency (or maybe not at all). If folk have chosen AVL trees in preference to RedBlack trees or vice-versa they have presumably done so for a good reason.
I thought, the common denominator (i.e. interface) are binary search trees.
I think we should be careful about making unwarranted assumptions about what people are going to be doing with these trees. You could use AVL trees to implement a purely functional queues for instance, in which case the tree elements are not ordered by value. I don't know how this would compare with other queue implementations, but I think the possiblity of things like this should at least be considered when designing "the" AVL tree library. Even in those cases where the elements are ordered, assuming that element types will all be instances of "Ord" is an unwarranted assumption and can be rather inconvenient. For many types there is no obvious unique ordering and in in such cases it is IMO far simpler to allow the appropriate comparison function to be passed as an explicit argument. By all means write high level "classyfied" wrappers around the AVL primitives, but the primitives should still be exposed for those that want them, and Data.Trees.AVL seems like the place to do it. Higher level libraries that try to provide a simpler unified view of all sorts of different trees or containers should be somewhere else I think. P.S. I find this data type very useful for writing sorting, searching and set related stuff that's as general purpose as (I think) it could possibly be.. -- Result of a combining comparison. data COrdering a = Lt | Eq a | Gt So set (list, tree or whatever) union looks like this -- Combines "equal" values union :: (a -> a -> COrdering a) -> Set a -> Set a -> Set a and intersection looks like this.. -- Combines "equal" values intersect :: (a -> b -> COrdering c) -> Set a -> Set b -> Set c Which I find more useful than.. intersect :: Ord a => Set a -> Set a -> Set a (taken from Data.Set) Regards -- Adrian Hey

union :: (a -> a -> COrdering a) -> Set a -> Set a -> Set a
What we "really" want here is being able to write code like this: let instance Ord A where { ... } in union (x :: Set A) (y :: Set A) It certainly needs some thinking to make this into a consistent proposal for a language extension ... Best regards, J.

On Mon, 5 Apr 2004, Adrian Hey wrote:
I think we should be careful about making unwarranted assumptions about what people are going to be doing with these trees. You could use AVL trees to implement a purely functional queues for instance, in which case the tree elements are not ordered by value.
Implementing democratic sequences with AVL (or any other balanced) trees is realistic. Dessy does it. Robert

On Wed, 31 Mar 2004, Christian Maeder wrote:
Rather than enforcing uniformity by a collection class (as proposed elsewhere), I would like uniformity at the module level wrt. exported functions and types. The hierarchy should allow for several different implemenations of one type with (almost) the same module interface.
Well, since this is a direct rival to the approach of Abstract Collections I should hit you with some hard arguments here. When I was young I also thought it was overkill to use dynamic binding to allow different implementations of one and the same specification. It seemed to me that a good way would be to choose at linking-time, so you always use the same interface-file and choose the implementation via the -l option. But modern programming methodology has abandoned the notion of separate interface files -- according to the "all in one document" principle we give the contracts and export lists directly in the code. The resulting question of how to "factor out" common specifications is answered by a simple, new mechanism that allows to factor our specifications _and_ code: that's inheritance. Deferred (jave lingo: abstract) classes in OO and type classes in Haskell can be used to _express formally_ the design of an interface (with semantics!) and this formal expression allows various automatic treatments that would otherwise have to be done by hand: it is used in type-checking, it is used to provide default implementations, it is used in the creation of documentation, and with DbC in Haskell it will be used for automatic tests. The module-based approach is simpler when you start small, but it just doesn't scale as well. E.g., where do I put a general-purpose function that works on all kinds of Sequences? And what should be its type? Not using inheritance leads to much redundance and no automatic way to check consistency. Of course, having huge contexts in types and sometimes ambigous types is a bit annoying, but that's no major problem, just the typical "formal noise" you'll always have in programming. Btw, approaches with subtyping don't have those problems, but they have others. What is astonishing: both approaches allow the same _designs_ to be expressed. That's why a can cite Bertrand Meyer's "Object-oriented software construction" (Prentice Hall, 1988) as the still up-to-date reference to design, even for (large) functional programs. Inheritance when used as a method is no fashion of the OO mode: it is an intrinsic part of software design. Without inheritance of implementation (default methods...) we'd need to choose for every function whether to implement it generically (using some primitives) or separately for each instance. Inheritance makes this choice oblivious (w?). People are complaining about too big classes, but where's the problem of this? Have you ever heard about Bertrand Meyer's "shopping cart" approach (not sure, whether that's the exact name)? The idea is, that if a class embodies a suitable abstraction, we can add as many features (functions) as we want as long as they fit the abstraction. Good abstraction ensures that we have no feature creep (i.e. complex monolithic features, instead of simple, composable ones). In object-orientation this is especially important, since any functions that are outside the class have to be called in a different way. For FP, on the other hand, users don't care at all whether a function is a class member or polymorphic: we can change that any time without the user noticing. And even implementors won't care much, since we'll have the default implementation. Who doesn't get at least a bit uneasy when looking at all the redundancy, in e.g. Edison's code? Okasaki has written some generic functions, but they have to be renamed manually in each module. All for the sake of efficiency! Bertrand Meyer did not propose to handle this via inheritance without ensuring that the compiler would eliminate all the indirections. And that was in 1985!
The current problem is agreeing on interfaces, while there exist quite a few implementations (from which we can pick all the good ones).
I think that Dessy at moment provides the best interface (with respect to generality and ease of use) and also some of the best implementations (in terms of algorithmic coverage, simplicity, little redundance, albeit not specific optimisations). Of course anyone may disagree. (Btw, documenting all the really innovative stuff in official publications will take some time, so if you want to wait...). Robert

On Fri, Apr 02, 2004 at 12:24:43PM +0200, Robert Will wrote:
I think that Dessy at moment provides the best interface (with respect to generality and ease of use) ...
That's a strong claim, and I think you need to justify that more. You may be getting there, but I don't think you're quite there yet. (In particular, there are several design decisions that I'm sure will be controversial once people get around to arguing with it; e.g., your reuse of functions currently in the standard Prelude.) Peace, Dylan

Adrian Hey wrote:
Maybe if we call what I've produced Multimedia.SDL.Core, though since it actually includes SDL_image and SDL_ttf also, maybe I should split these out to produce.. Multimedia.SDL.Core Multimedia.SDL.Image Multimedia.SDL.TTF so anybody who felt inclined to write a binding for one of the many SDL extension libraries could use Multimedia.SDL.<whatever> (Or maybe my "Core" binding should still be just Multimedia.SDL?)
"Core" is not very descriptive IMHO, what about staying close to the structure of the SDL library documentation (e.g. http://sdldoc.csn.ul.ie/): Multimedia.SDL.General Multimedia.SDL.Video Multimedia.SDL.Window Multimedia.SDL.Events ... and using Multimedia.SDL as a collector module for everything below it? Cheers, S.

On Wednesday 31 Mar 2004 5:02 pm, Sven Panne wrote:
Adrian Hey wrote:
Maybe if we call what I've produced Multimedia.SDL.Core, though since it actually includes SDL_image and SDL_ttf also, maybe I should split these out to produce.. Multimedia.SDL.Core Multimedia.SDL.Image Multimedia.SDL.TTF so anybody who felt inclined to write a binding for one of the many SDL extension libraries could use Multimedia.SDL.<whatever> (Or maybe my "Core" binding should still be just Multimedia.SDL?)
"Core" is not very descriptive IMHO, what about staying close to the structure of the SDL library documentation (e.g. http://sdldoc.csn.ul.ie/):
Multimedia.SDL.General Multimedia.SDL.Video Multimedia.SDL.Window Multimedia.SDL.Events ...
What I'm proposing to do is 3 separate packages.. Multimedia.SDL(.Core perhaps) Multimedia.SDL.Image Multimedia.SDL.TTF ..because I think it would be nice to have 1:1 correspondance between Haskell packages and SDL packages (SDL,SDL_image,SDL_ttf). This makes dependencies clear and means Haskellers won't have to install SDL stuff they don't need. I think the only real issue is should the core (I.E. the SDL binding) actually have a .Core suffix? Let's say it didn't. In the Multimedia directory I have.. * A directory called SDL * A single Haskell source file called SDL.hs which wraps the API defined in the various Haskell source files in the SDL directory. Within the SDL directory the naming of individual source files does indeed follow the SDL documentation, as you suggest (well up to a point anyway). But these are all *.hs files that are part of a single library (package). The naming convention above identifies distinct SDL related libraries (which will also have corresponding directories and *.hs files of course, but that's not relevant here AFAICS). The point is that the API's of Multimedia.SDL.Image and Multimedia.SDL.TTF are not exported by Multimedia.SDL, as some might expect. Maybe having an explicit .Core suffix would be clearer. (Though we have a similar situation with Foreign and Foreign.C for example, so I guess it's not really an issue). Regards -- Adrian Hey

Adrian Hey wrote:
What I'm proposing to do is 3 separate packages. [...] This makes dependencies clear and means Haskellers won't have to install SDL stuff they don't need.
Sorry, I misunderstood you. Having separate packages makes much sense for this scenario, indeed.
I think the only real issue is should the core (I.E. the SDL binding) actually have a .Core suffix?
I have a small brain and therefore I like simple rules like "Every module Foo simply re-exports the modules Foo.*". :-) Using the .Core suffix would make things easy: * We have an SDLCore package with modules rooted at Multimedia.SDL.Core (a collector module) with sub-modules Multimedia.SDL.Core.Video, ... * Same for an SDLImage package at Multimedia.SDL.Image * SDLTTF at Multimedia.SDL.TTF ... A "super collector" module Multimedia.SDL would not be a good idea in this case, because its export list would depend on the available SDL stuff.
[...] Though we have a similar situation with Foreign and Foreign.C for example, so I guess it's not really an issue).
Well, Foreign is a bad example, which has been discussed on this list recently. When we have versioned packages, Foreign should re-export all the modules below it, nothing more and nothing less IMHO. Cheers, S.

Am Sonntag, 4. April 2004 16:51 schrieb Sven Panne:
[...]
I have a small brain and therefore I like simple rules like "Every module Foo simply re-exports the modules Foo.*". :-)
I've never used this strategy. In my opinion, it makes much sense if a module Foo is about general foo things whereas its submodules are about more specific things.
[...]
Wolfgang

Wolfgang Jeltsch wrote:
Am Sonntag, 4. April 2004 16:51 schrieb Sven Panne:
I have a small brain and therefore I like simple rules like "Every module Foo simply re-exports the modules Foo.*". :-) I've never used this strategy. In my opinion, it makes much sense if a module Foo is about general foo things whereas its submodules are about more specific things.
That's no contradiction to my rule, e.g. Graphics.Rendering.OpenGL is about *all* OpenGL stuff, while Graphics.Rendering.OpenGL.GL is about GL and Graphics.Rendering.OpenGL.GLU is about GLU. Perhaps I should explain a little bit more what IMHO is a "good use" of the hierarchical structure: * "collector" modules: These are a necessity for larger APIs, otherwise you can easily have dozens of closely related imports. Nobody argued against this use, IIRC, and we already have a lot of examples of it. * "selector" modules: There are different implementations Foo.A and Foo.B of basically the same API, but it's not clear (yet) which one is better. So Foo simply re-exports one of Foo.A and Foo.B as the default for people who don't care, but there is still the possibility of using a specific one. Text.PrettyPrint is an example of this use, although there's currently only one specific implementation. Another example is Data.STRef, Data.STRef.Lazy, and Data.STRef.Strict, but the imports are a bit "upside-down" here, something we should probably change. * A collection of only loosely related modules Foo.A, Foo.B, ...: Having a module Foo wouldn't make much sense in this case. A good example for this is the Data hierarchy. So I'm not that narrow-minded by supporting only a single rule... :-) But we should really try to avoid a structure with no clear superset/subset relationship like, alas, the Foreign module. Cheers, S.

Am Montag, 5. April 2004 10:49 schrieben Sie:
Wolfgang Jeltsch wrote:
Am Sonntag, 4. April 2004 16:51 schrieb Sven Panne:
I have a small brain and therefore I like simple rules like "Every module Foo simply re-exports the modules Foo.*". :-)
I've never used this strategy. In my opinion, it makes much sense if a module Foo is about general foo things whereas its submodules are about more specific things.
That's no contradiction to my rule, e.g. Graphics.Rendering.OpenGL is about *all* OpenGL stuff, while Graphics.Rendering.OpenGL.GL is about GL and Graphics.Rendering.OpenGL.GLU is about GLU.
I think, we mean different things. You talk about Foo containing *all* foo stuff whereas I talk about Foo containing the *basic* foo stuff or suff for general foos or whatever. One example is a hierarchy for graph handling code, I used lately. The module <prefix>.Graph contains code for directed graphs, <prefix>.Graph.Acyclic contains a type for the special case of acyclic graphs, etc. Another example are modules about URIs, which I'm currently developing. <prefix>.URI contains the URI type, <prefix>.URI.Scheme contains a type for URI schemes, <prefix>.URI.Hierarchical provides support for the special case of hierarchical URIs and so on.
Perhaps I should explain a little bit more what IMHO is a "good use" of the hierarchical structure:
* "collector" modules: These are a necessity for larger APIs, otherwise you can easily have dozens of closely related imports. Nobody argued against this use, IIRC, and we already have a lot of examples of it.
I don't know if dozens of closely related imports are such a bad thing. The problem with your approach is that it doesn't seem to work if certain names are defined in several of the collected modules. For example, I cannot see how you would create a DData collector module. Another problem I see is that you cannot use the module Foo for general things (see above) which is sometimes useful.
[...]
Cheers, S.
Wolfgang
participants (10)
-
Adrian Hey
-
Christian Maeder
-
dpt@lotus.bostoncoop.net
-
Graham Klyne
-
Johannes Waldmann FbIMN
-
Robert Will
-
Ross Paterson
-
Simon Marlow
-
Sven Panne
-
Wolfgang Jeltsch