
Sorry for this stupid question put there must be reasons I don't know. I've been thinking a lot about packaging/ dependency handling etc the last days. Haskell is one of the most typesafe and expressive languages, right? Now we need a haskell compiler/ interpreter to run Setup.hs. So why not combine both and use some kind of cabal combinator library? I'll try to implement a prototype although knowing there are lots of people knowing how to do this better. module Setup where import CabalBuildProposal helloWorld = haskell-executable $ do setName "helloworld" sourceDir "src" $ mainIs "HelloWorld.hs" addDependencies = case stringOption "pretty_print_lib" of "A" : [LibVersionRange "A" "1.0 - 2.0"] "B" : [LibVersionRange "B" "1.0 - 2.0"] package = do setAuthor = "Marc Weber" addAtom helloWorld preprocess = defaultHaskellPreprocess build = preprocess >>= defaultHaskellBuild rpm = build >>= defaultRPM install = defaultHaskellInstall haddock = defaultHaddock targets = [ ("preprocessOnly", preprocess) , ("build", build ) , ("install", build >>= install) , ("rpm", rpm ) , ("haddock", preprocess >>= haddock) ] main = do handle package targets using preprocessors might be done in this way: addExposedModules $ map preprocessByCPP $ modulesByRegex "src/**/*.hs" I think you get the idea why this approach might be much more powerful? The package mantainers of ght2hs and wkhaskell have both trouble makeing their project work with cabal.. So why do we limit ourself using cabal files like the existing ones? I think you've noticed the line addDependencies = case stringOption "pretty_print_lib" of This should use the correct dependency if the option has already been set by cmdline or config file else ask the user or choose the first but noticing the user by printing a message like this: unset option "pretty_print_lib", defaulting to "A" preprocess should be passed all configuration options and return a list of source files, build should get the list of source file and return a list of executables which are installed by install straightforward, isn't it? Thus the right build/ install whatsoever step would be choosen not by defining hooks but by the haskell type system. This way the packaging system user can plug in his own implementation everywhere. Any ideas, comments? Anyone out there who wants to join and help implementing this idea? Marc

Hi Marc, [Snip]
Any ideas, comments?
Anyone out there who wants to join and help implementing this idea?
I'd ask why there is a Setup.hs file at all, a nice textual declarative form seems much more sensible. You can encode everything in Haskell, but you probably shouldn't... First off, its harder to read, harder to parse (unless you happen to be a Haskell compiler) and just not as straight forward. Should you be able to pick which library version you want based on the day of the week? Should your package name be allowed to be a random string which changes each time? It is a cute idea (less different forms), but I don't think it fits the problem in this case. Thanks Neil

Marc points out that the expressiveness of the Cabal language is
insufficient for some packages, and a DSEL would be more expressive. I have
the same problem and still have to resort to makefiles to augment my .cabal
files.
DSELs also provide sharing/reuse. I know my Cabal specs are similar, and
yet I cannot capture that commonality.
Using a DSEL does not imply that it route through IO, though from Marc's
examples I'm guessing he has IO in mind. Avoiding IO would address your
points about day of week and random strings.
So I hope Marc's suggestion gets some consideration.
- Conal
On 1/9/07, Neil Mitchell
Hi Marc,
[Snip]
Any ideas, comments?
Anyone out there who wants to join and help implementing this idea?
I'd ask why there is a Setup.hs file at all, a nice textual declarative form seems much more sensible. You can encode everything in Haskell, but you probably shouldn't...
First off, its harder to read, harder to parse (unless you happen to be a Haskell compiler) and just not as straight forward. Should you be able to pick which library version you want based on the day of the week? Should your package name be allowed to be a random string which changes each time?
It is a cute idea (less different forms), but I don't think it fits the problem in this case.
Thanks
Neil _______________________________________________ cabal-devel mailing list cabal-devel@haskell.org http://www.haskell.org/mailman/listinfo/cabal-devel

On Tue, Jan 09, 2007 at 07:41:57PM -0800, Conal Elliott wrote:
Marc points out that the expressiveness of the Cabal language is insufficient for some packages, and a DSEL would be more expressive. Sorry, I've never heard abaut DSEL yet. I still feel like beening a total beginner.. ;) But I'll try to fill this lack of knowledge. I was thinking in IO monads as I didn't know something better..
Conal : Can you help me lifting my skills and tell me in some sentences how a build system could benefit from DSELs? Marc

Hi Marc.
See Paul Hudak's position
paperhttp://www.cs.yale.edu/homes/hudak-paul/hudak-dir/ACM-WS/position.htmlon
DSELs, where you'll find definition, motivation & examples. See also
Peter
Landin http://en.wikipedia.org/wiki/Peter_J._Landin's "Next 700" paper.
If you have questions, please ask!
BTW, I hear both "EDSL" and "DSEL", and I don't recall which is more in
vogue and what reasons are for one or the other. Maybe Paul or someone
could comment.
Cheers, - Conal
On 1/10/07, Marc Weber
On Tue, Jan 09, 2007 at 07:41:57PM -0800, Conal Elliott wrote:
Marc points out that the expressiveness of the Cabal language is insufficient for some packages, and a DSEL would be more expressive. Sorry, I've never heard abaut DSEL yet. I still feel like beening a total beginner.. ;) But I'll try to fill this lack of knowledge. I was thinking in IO monads as I didn't know something better..
Conal : Can you help me lifting my skills and tell me in some sentences how a build system could benefit from DSELs?
Marc _______________________________________________ cabal-devel mailing list cabal-devel@haskell.org http://www.haskell.org/mailman/listinfo/cabal-devel

On Fri, Jan 12, 2007 at 01:23:37PM -0800, Conal Elliott wrote:
Hi Marc. See Paul Hudak's [1]position paper on DSELs, where you'll find definition, motivation & examples. See also [2]Peter Landin's "Next 700" paper. If you have questions, please ask! BTW, I hear both "EDSL" and "DSEL", and I don't recall which is more in vogue and what reasons are for one or the other. Maybe Paul or someone could comment. Cheers, - Conal Did I get it right this way? I'm up to create a new DSEL, which is no new language feature but a an application of the language to a particualr problem resulting in some kind of library (Thus beeing specialized and more abstract?)
Marc

"Conal Elliott"
Marc points out that the expressiveness of the Cabal language is insufficient for some packages, and a DSEL would be more expressive. I have the same problem and still have to resort to makefiles to augment my .cabal files.
The original design of Cabal was more like Marc suggests. There was only the Setup file and no .cabal file, and my hope was that we'd build an EDSL for package configurations. Original cabal code would probably look like: main = defaultMain defaultPackageDescription{ name="foo" , synopsys="bar"} etc. Then I was hoping it would evolve to an EDSL. But most people didn't like this design. My argument was that if we created a a.cabal file, eventually the design would get more and more complex, so why not just start out with Haskell, which would give us room to grow :) But there are also lots of advantages to having the .cabal file. Maybe someone can dig up the debate on the libraries mailing list from a few years back. Anyway, with the hooks interface, you can override just about all of cabal's behavior (including inputting the description file) so there's pleanty of room to experiment with something like an EDSL. Unfortunitely your package would not be cabal-compliant without a .cabal file. We are moving more in the other direction... keeping all of the information in .cabal and not requiring a Setup.lhs file. That seems to be easier for most people. peace, isaac

On Wed, 10 Jan 2007, Isaac Jones wrote:
"Conal Elliott"
writes: Marc points out that the expressiveness of the Cabal language is insufficient for some packages, and a DSEL would be more expressive. I have the same problem and still have to resort to makefiles to augment my .cabal files.
The original design of Cabal was more like Marc suggests. There was only the Setup file and no .cabal file, and my hope was that we'd build an EDSL for package configurations. Original cabal code would probably look like:
main = defaultMain defaultPackageDescription{ name="foo" , synopsys="bar"}
etc.
Then I was hoping it would evolve to an EDSL.
I also suggested to provide installers in form of Haskell modules. Simon Marlow responded, that this would prohibit manipulation of configuration files (that is, the .cabal files) via GUI.

On Wed, Jan 10, 2007 at 06:53:43AM -0800, Isaac Jones wrote:
The original design of Cabal was more like Marc suggests. There was only the Setup file and no .cabal file, and my hope was that we'd build an EDSL for package configurations. Original cabal code would probably look like:
main = defaultMain defaultPackageDescription{ name="foo" , synopsys="bar"} complex, so why not just start out with Haskell, which would give us room to grow :) But there are also lots of advantages to having the .cabal file. Maybe someone can dig up the debate on the libraries mailing list from a few years back.
Anyway, with the hooks interface, you can override just about all of cabal's behavior
Sure I can. But I'd like to have it the other way round with a function: readDescription from Cabal file.. Thanks for clarifying. Isaac: I'm new to this project cabal/ hackage. So I need to know wether this is still the right place to discuss this (because this descission has been made some time ago and Cabal seems to move in a direction I don't like (using text/ cabal file like configurations) Or is the right thing to do fork and create another mailinglist if anyone is interested, too? Anyway it would be cool to put these kinds of "descission" having been made long time ago somewhere on the cabal page for information why Cabal is the way it is. When I come up with something useful I'll post here again. peace, thanks, .. ;) Marc

On Wed, 10 Jan 2007, Marc Weber wrote:
On Wed, Jan 10, 2007 at 06:53:43AM -0800, Isaac Jones wrote:
The original design of Cabal was more like Marc suggests. There was only the Setup file and no .cabal file, and my hope was that we'd build an EDSL for package configurations. Original cabal code would probably look like:
main = defaultMain defaultPackageDescription{ name="foo" , synopsys="bar"} complex, so why not just start out with Haskell, which would give us room to grow :) But there are also lots of advantages to having the .cabal file. Maybe someone can dig up the debate on the libraries mailing list from a few years back.
Anyway, with the hooks interface, you can override just about all of cabal's behavior
Sure I can. But I'd like to have it the other way round with a function: readDescription from Cabal file..
Actually, you can do this. Probably the biggest part of Cabal is a Haskell library. You can read package description or you can create a PackageDescription manually and then call some of the Cabal routines.

Marc Weber
Isaac: I'm new to this project cabal/ hackage. So I need to know wether this is still the right place to discuss this (because this descission has been made some time ago and Cabal seems to move in a direction I don't like (using text/ cabal file like configurations)
Or is the right thing to do fork and create another mailinglist if anyone is interested, too?
I certainly wouldn't encourage you to fork. I think that the design of cabal is quite good, and the closest to what users actually want. I think that at this point, it's a bikeshed (and one that's already been built (and painted)): http://www.unixguide.net/freebsd/faq/16.19.shtml There are more exciting and interesting things to work on now. The action is in cabal-install and hackage; building layered tools to get Haskell programs into the hands of end-users. But if you are seriously interested in the area of a domain specific language for packages, I'd encourage you to make it something that would work within the context of the hooks, so that people can write nicer Setup scripts, and it should be pretty neutral to whether or not there's a package description file. Writing setup scripts isn't too easy these days, and if you can come up with something to make it better, that would be great. Remember: Cabal isn't only the build infrastructure, it's also the metadata format that tools like Hackage use. If you decide to combine data and code, you will no longer be able to manipulate the data with another tool.
Anyway it would be cool to put these kinds of "descission" having been made long time ago somewhere on the cabal page for information why Cabal is the way it is.
Feel free to do so on the wiki if you dig stuff up.
When I come up with something useful I'll post here again.
Feel free! peace, isaac

On 1/10/07, Isaac Jones
... Remember: Cabal isn't only the build infrastructure, it's also the metadata format that tools like Hackage use. If you decide to combine data and code, you will no longer be able to manipulate the data with another tool.
I'm worried and confused about this conclusion. I want to address my confusion first, and maybe the worry will be handled. By "data" vs "code", I'm guessing you mean simple first-order values, and mainly strings, vs everything else (especially functions). But I wonder if instead you mean any Haskell value (including functions) vs the content of a .hs file? Maybe I'd have a firmer grasp of this issue if I could had in mind an example of such a metadata-manipulating tool. Would someone please suggest one? Regards, - Conal

"Conal Elliott"
On 1/10/07, Isaac Jones
wrote: ... Remember: Cabal isn't only the build infrastructure, it's also the metadata format that tools like Hackage use. If you decide to combine data and code, you will no longer be able to manipulate the data with another tool.
I'm worried and confused about this conclusion. I want to address my confusion first, and maybe the worry will be handled.
By "data" vs "code", I'm guessing you mean simple first-order values, and mainly strings, vs everything else (especially functions). But I wonder if instead you mean any Haskell value (including functions) vs the content of a .hs file?
I'm not sure what you mean here. What I'm talking about is that if you have a programatic way of producing the package description, then you no longer have a way of "reading" that package description from another tool.
Maybe I'd have a firmer grasp of this issue if I could had in mind an example of such a metadata-manipulating tool. Would someone please suggest one?
Visual Haskell, HackageDB, cabal2rpm, and dh_haskell are all tools that read the .cabal file and perform operations based on the package metadata. These tools would have to be Haskell interpreters if they wanted to read a .hs file and derive the package description from that. peace, isaac

Remember: Cabal isn't only the build infrastructure, it's also the metadata format that tools like Hackage use. If you decide to combine data and code, you will no longer be able to manipulate the data with another tool. Visual Haskell, HackageDB, cabal2rpm, and dh_haskell are all tools that read the .cabal file and perform operations based on the package metadata. These tools would have to be Haskell interpreters if they wanted to read a .hs file and derive the package description from that. Then the way to go would be: add a target "create-editor-readable-package-description". So still now reason to do this work on your own..
This is not really a pro for cabal files IMHO. Marc

Hi
Then the way to go would be: add a target "create-editor-readable-package-description". So still now reason to do this work on your own..
So now there is a standardised way to convert Haskell code to a package description which isn't Haskell code. All you have shown here is that there can be two equivalent encodings, one in Haskell, and one in some special purpose language (Cabal). The question is: 1) Is it easier to read Haskell or Cabal? Answer is almost certainly Cabal, by a bit. 2) Can you get rooted getting the license out of an application. Cabal, no, Haskell yes. Thanks Neil

Marc Weber wrote:
I'm not sure wether I get this sentence right. What do you mean by "getting rooted" ?
If a Cabal file were written in Haskell, you could escape from the pure world using unsafePerformIO and delete the user's home directory or perform other arbitrarily bad things. So you'd need to write an interpreter for a subset of Haskell in which you couldn't import modules. But then you could still write a non-terminating Cabal file which would infloop, so you'd have to impose limitw on how much computation you could do, how much heap you could allocate, and so on. Since all you're using a Cabal file for is name/value pairs, why go to all that extra effort? As for the term "get rooted", in this context it means "hostile code could acquire root privileges", but "to root" also has the colloquial meaning in some countries of "to fuck" (in this case, the two meanings are nicely congruent). So be careful who you use it with :-)

Hi Bryan,
From your argument I conclude that Haskell code unsafe in general, not just for package specification. I'd like to see us address the general problem, rather than avoid it here and there. I hate to see sacrifice the benefits of declarative DSELs (reuse, expressiveness, etc) and still not root out (hmm) the core problem of safety.
I also wonder: if you don't trust my package spec code, why would you trust
my library code? My package spec is usually very simple, and when it's not,
I'd welcome your scrutiny and help in making it simpler and more easily
trusted.
If I were confident that the problem Cabal address is covered by name/value
pairs, I might agree that functional programming is overkill. (Though I'd
still dislike redundancy among my .cabal files.) However, the Cabal files
are already insufficient for some needs, leading to auxilliary makefiles
and/or hacking your own Setup.lhs. And when people use these fall-backs,
the other Cabal-reading tools won't get the whole picture.
Cheers, - Conal
P.S. Thanks for the language tip. I had no idea.
On 1/13/07, Bryan O'Sullivan
Marc Weber wrote:
I'm not sure wether I get this sentence right. What do you mean by "getting rooted" ?
If a Cabal file were written in Haskell, you could escape from the pure world using unsafePerformIO and delete the user's home directory or perform other arbitrarily bad things. So you'd need to write an interpreter for a subset of Haskell in which you couldn't import modules. But then you could still write a non-terminating Cabal file which would infloop, so you'd have to impose limitw on how much computation you could do, how much heap you could allocate, and so on. Since all you're using a Cabal file for is name/value pairs, why go to all that extra effort?
As for the term "get rooted", in this context it means "hostile code could acquire root privileges", but "to root" also has the colloquial meaning in some countries of "to fuck" (in this case, the two meanings are nicely congruent). So be careful who you use it with :-)

Hi
From your argument I conclude that Haskell code unsafe in general, not just for package specification.
That is indeed true. Donald has jumped through many hoops to try and make the code safer for Lambdabot. If you really want truely safe code, the best thing to do would be to add a patch to Yhc with a -sandbox flag which would be relatively easy to implement, and could give solid guarantees about what your code does.
If I were confident that the problem Cabal address is covered by name/value pairs, I might agree that functional programming is overkill. (Though I'd still dislike redundancy among my .cabal files.) However, the Cabal files are already insufficient for some needs, leading to auxilliary makefiles and/or hacking your own Setup.lhs. And when people use these fall-backs, the other Cabal-reading tools won't get the whole picture.
True, another reason to make the .cabal file more complete - things like preprocessors should not be in Setup.hs, for example.
P.S. Thanks for the language tip. I had no idea.
Me neither on the second meaning! I just use the term "get rooted" to mean someone breaks into your computer in malicious ways, since on my OS of choice there is no root account, only Admin, and most people run as Admin. Thanks Neil

True, another reason to make the .cabal file more complete - things like
preprocessors should not be in Setup.hs, for example.
How "complete" will be enough? My guess is Turing complete. When we get to
that point, I'd like the .cabal file to look like Haskell.
- Conal
On 1/13/07, Neil Mitchell
Hi
From your argument I conclude that Haskell code unsafe in general, not just for package specification.
That is indeed true. Donald has jumped through many hoops to try and make the code safer for Lambdabot. If you really want truely safe code, the best thing to do would be to add a patch to Yhc with a -sandbox flag which would be relatively easy to implement, and could give solid guarantees about what your code does.
If I were confident that the problem Cabal address is covered by name/value pairs, I might agree that functional programming is overkill. (Though I'd still dislike redundancy among my .cabal files.) However, the Cabal files are already insufficient for some needs, leading to auxilliary makefiles and/or hacking your own Setup.lhs. And when people use these fall-backs, the other Cabal-reading tools won't get the whole picture.
True, another reason to make the .cabal file more complete - things like preprocessors should not be in Setup.hs, for example.
P.S. Thanks for the language tip. I had no idea.
Me neither on the second meaning! I just use the term "get rooted" to mean someone breaks into your computer in malicious ways, since on my OS of choice there is no root account, only Admin, and most people run as Admin.
Thanks
Neil

On Sat, 13 Jan 2007, Conal Elliott wrote:
Hi Bryan,
From your argument I conclude that Haskell code unsafe in general, not just for package specification. I'd like to see us address the general problem, rather than avoid it here and there. I hate to see sacrifice the benefits of declarative DSELs (reuse, expressiveness, etc) and still not root out (hmm) the core problem of safety.
Me too. See e.g. verification of homework Haskell programs. Suppressing IO is simple, suppressing unsafePerformIO - how to do that?
I also wonder: if you don't trust my package spec code, why would you trust my library code? My package spec is usually very simple, and when it's not, I'd welcome your scrutiny and help in making it simpler and more easily trusted.
Or - why do you trust Setup.lhs?

On Sat, Jan 13, 2007 at 12:57:33PM -0800, Conal Elliott wrote:
I also wonder: if you don't trust my package spec code, why would you trust my library code?
As an example, hackage can look at your .cabal file and extract the meta-information to build a webpage about your library, add the info to its searchable database so users can search for it, etc. (Assuming your Setup.[l]hs isn't /too/ wacky). We don't want hackage to be executing anything anyone uploads automatically, though (although as pointed out elsewhere in this thread, with a little effort we could attempt to make it safe to do so). Thanks Ian

Visual Haskell, HackageDB, cabal2rpm, and dh_haskell are all tools that read the .cabal file and perform operations based on the package metadata.
In which information are they particularely interested? Am I right that they the main goal is getting to know which are the source files and which dependencies to add? Neil, I begin to see: Its possible to add dependencies automatically using IDEs to cabal files, but not to haskell files.. Thus if you use liftM an IDE could add import Monad as well as build-depends: mtl Marc

On 1/12/07, Isaac Jones
wrote:
These tools would have to be Haskell interpreters if they wanted to read a
.hs file and derive the package description from that.
Thanks, Isaac. This statement helps me a lot. Now I think you really do mean "code" in the literal sense (the second one I suggested), as in Haskell code ("the content of a .hs file"). (I've often heard people say "code" or " expressions" when they mean the denotations of such things, especially in regard to lazy languages.) What I'm talking about is that if you have a programatic way of producing
the package description, then you no longer have a way of "reading" that package description from another tool.
Maybe I'm missing something, but I think I see a simple way to do just that.
The "programatic way of producing" is the Haskell code, and "the package
description" is the data. That data might be higher-order, with no textual
description other than the original source code. Another tool "reads" in
that description by being passed the data. Maybe that means running the code
(e.g., loaded dynamically) or unpickling a persisted version, or simply by
being in a function composition chain.
I'm loving my experience with Cabal so far, and I'm grateful to you and
others for creating and evolving it. I'll keep using it, even if it's not
painted my favorite color. And I can't help but notice that I have to repeat
myself (across Cabal files) and later go back and change all of my Cabal
(and make) files when I better understand the tool and my own needs. And in
spite of saying more than I want to in a Cabal file (repetition), I still
can't say all I want to say, so I resort to makefiles. In Pavlovian style, I
can't help wondering if a lovely little Haskell EDSL might give me more
succinctness, more flexibility, and freedom from those crufty old makefiles.
Cheers, - Conal
P.S. True Confession: I enjoy makefile hacking, in a guilty pleasure sort of
way.
On 1/12/07, Isaac Jones
"Conal Elliott"
writes: On 1/10/07, Isaac Jones
wrote: ... Remember: Cabal isn't only the build infrastructure, it's also the metadata format that tools like Hackage use. If you decide to combine data and code, you will no longer be able to manipulate the data with another tool.
I'm worried and confused about this conclusion. I want to address my confusion first, and maybe the worry will be handled.
By "data" vs "code", I'm guessing you mean simple first-order values, and mainly strings, vs everything else (especially functions). But I wonder if instead you mean any Haskell value (including functions) vs the content of a .hs file?
I'm not sure what you mean here. What I'm talking about is that if you have a programatic way of producing the package description, then you no longer have a way of "reading" that package description from another tool.
Maybe I'd have a firmer grasp of this issue if I could had in mind an example of such a metadata-manipulating tool. Would someone please suggest one?
Visual Haskell, HackageDB, cabal2rpm, and dh_haskell are all tools that read the .cabal file and perform operations based on the package metadata. These tools would have to be Haskell interpreters if they wanted to read a .hs file and derive the package description from that.
peace,
isaac

Conal Elliott wrote:
On 1/12/07, Isaac Jones
mailto:ijones@syntaxpolice.org> wrote: These tools would have to be Haskell interpreters if they wanted to read a .hs file and derive the package description from that.
Thanks, Isaac. This statement helps me a lot. Now I think you really do mean "code" in the literal sense (the second one I suggested), as in Haskell code ( "the content of a .hs file"). (I've often heard people say "code" or "expressions" when they mean the denotations of such things, especially in regard to lazy languages.)
What I'm talking about is that if you have a programatic way of producing the package description, then you no longer have a way of "reading" that package description from another tool.
Maybe I'm missing something, but I think I see a simple way to do just that. The "programatic way of producing" is the Haskell code, and "the package description" is the data. That data might be higher-order, with no textual description other than the original source code. Another tool "reads" in that description by being passed the data. Maybe that means running the code (e.g., loaded dynamically) or unpickling a persisted version, or simply by being in a function composition chain.
So there are two issues, one of which has been pointed out already: - trust: Hackage doesn't want to run arbitrary code to extract a package description, for example. It could, by using a sandbox of some variety, but that's a lot of effort to go to just to extract the package metadata. - tools that not only read, but write the package metadata. For example, in Visual Haskell you can load up an existing package in the environment, add a few modules, and save it again as a valid Cabal package. Sure we can only do this as long as you don't use Setup.lhs for anything non-trivial, but that's a large class of packages. As Isaac already said, the original design was code-only. It was due to the Visual Haskell requirements that we decided to move to a mixture of code & data. Finding the right place to put the boundary has been tricky, and is necessarily a compromise: we want to support as many packages as possible with just .cabal, and yet not complicate the language (and its implementation) too much. Now that we're getting into conditionals and suchlike, things are getting even murkier. Cheers, Simon

http://www.haskell.org/pipermail/glasgow-haskell-users/2007-January/011854.h... This mail posted to glasgow-haskell-users by Samuel has been forwarded to libraries@haskell.org by Simon Peyton Jones as well Cheers Marc

On Wed, Jan 10, 2007 at 01:39:08AM +0000, Neil Mitchell wrote:
Hi Marc,
[Snip]
Any ideas, comments?
Anyone out there who wants to join and help implementing this idea?
I'd ask why there is a Setup.hs file at all, a nice textual declarative form seems much more sensible.
Thus you are asking why there is support for hooks at all? Sorry I can't follow you, sir! You can encode everything
in Haskell, but you probably shouldn't...
First off, its harder to read, harder to parse (unless you happen to be a Haskell compiler) Aeh.. Why are you programming in haskell, than? Again I can't follow.. If this is hard to parse, would you mind pointing me to the lines you had real troubl understanding them?
Or do you think its hard to read / use for total haskell beginners? If so its no problem to also provide a function as cabal does has it: replace the line handle congfig targets by handleFromSimpleTextFile and every one will be happy? and just not as straight forward. Should you be
able to pick which library version you want based on the day of the week? Should your package name be allowed to be a random string which changes each time? Why not ? If somewody likes to? But the library won't be used than.. He can do this now, too. He/ she has to provide a different cabal file each day.. This shouldn't be any problem using php name: <?=randomString?>
How do you protect people from using libs with rubbish code? I can't do anything moro than quote yourself: " I would demand at the very least a real name, email address - but really, in an online world those things are nearly useless. I guess the only thing to do is to trust that people who have learnt enough about monads and IO to hijack Haskell things probably realise how cool Haskell is... " (quoted from http://www.haskell.org/pipermail/libraries/2007-January/006662.html) I think this might apply here, too ;) If you don't unerstand how I think this applies aske again. But I think its not much effort convincing me to write simple text files ;) I adbmit that I plan to use this packaging system not just for haskell, but also for compiling microcontroller code etc.. I like Makefiles but I also hate them.. Thus textfiles justd wouldn't be expressive enough for my needs. Thanks Marc

addDependencies = case stringOption "pretty_print_lib" of
This should use the correct dependency if the option has already been set by cmdline or config file else ask the user or choose the first but noticing the user by printing a message like this:
unset option "pretty_print_lib", defaulting to "A"
preprocess should be passed all configuration options and return a list of
Marc Weber
build should get the list of source file and return a list of executables which are installed by install Marc
I like your idea. I had thought about something similar. See this post (http://ashish.typepad.com/ashishs_niti/2007/03/learning_haskel.html). I have put up a Haskell project for Google Summer of Code 2007. I would love to work on this or related idea.

On Mon, Mar 12, 2007 at 05:43:00AM +0000, Ashish Hanwadikar wrote:
addDependencies = case stringOption "pretty_print_lib" of
This should use the correct dependency if the option has already been set by cmdline or config file else ask the user or choose the first but noticing the user by printing a message like this:
unset option "pretty_print_lib", defaulting to "A"
preprocess should be passed all configuration options and return a list of
Marc Weber
writes: source files, build should get the list of source file and return a list of executables which are installed by install Marc
I like your idea. I had thought about something similar. See this post (http://ashish.typepad.com/ashishs_niti/2007/03/learning_haskel.html).
I have put up a Haskell project for Google Summer of Code 2007. I would love to work on this or related idea.
Hi Ashish Hanwadikar! Have also a look at this project (Duncan has pointed me to it in a previous post (" debugging support - multidimensional package selection ... ") on this list).. I hadn't had enough to time to learn it thoroughly but it looks really promising. Its task is not to build a haskell application, but to manage dependencies and ensure that they are installed by their own installers (make, scons, whatsover) a little bit like the portage system of gentoo but it seems to be much faster. You can also have installed arbitrary amounts of the same application differing only in the version.. quote Duncan: " For some related work you might want to look at Nix: http://www.cs.uu.nl/~eelco/pubs/ " I have put some effort into my approach and my project can build ghc executables now, read options from config files. The main advantage over cabal is this general concept of a package: data Package = Package { metaInfo :: MetaInfo , actions :: Actions } type Actions = [(String, Action)] data Action = Action { -- on which actions does this action depend? actionDependencies :: [ String ] , buildDependencies :: CheckedDeps , runDependencies :: CheckedDeps , checkRerun :: CheckRerun , actionToRun :: ExecutionMonad ActionResult } Especially for haskell the actions look like this: Pkg (HPS.Lang.Haskell.metaInfo hac) $ [ -- these actions will be availible ( "listSourceFiles", empty { actionToRun = let list = showModules ms in do liftIO $ putStrLn list return $ ActionResult list } ) -- this is needed by IDEs ? , ( "compile", empty { actionToRun = compile' } ) , ( "install", empty { actionToRun = install' , actionDependencies = ["compile"] } ) -- , haddock to be implemented -- , bindist -- binary distribution -- , dist -- disribution of source files (in general only preprocessed files are included here ?) -- , clean ] Note that the action "install" depends on "compile" and compile will depend on "preprocess" which in turn will depend on "get sources" or something similar. A big advantage is that you can add new acitons running configure/make, building preprocessors, running/ building test applications etc. Of course this all is possible using cabal, too. But you have to use hooks which might give you some troubles if you want to build your package in a non standard way (eg wxhaskell, ghc itself? (multistage build), hdirect (two stage build if you need com support on windows)) Drawaback: Needs recent ghc version, a modified DrIft Preprocessor and HList. I didn't konw how to put definitions in different modules because of mutable recursive dependecies. Do pretty much seems to be in one file ;) The 'dependency' analysis of those actions is done in one line: (concatMap (reverse . concat . levels) . dfs (graph ag)) idxs which takes the build graph and finds all dependencies ;) I've stopped working on it because I think nix does solve many issues I want to have in a much better way such as installing arbitrary software packages. But I need to learn more about it before I do know how to proceed. So at the moment I think I need another build tool but no longer another cross-platform packaging tool. I'd like to share my work but I'm not sure wether its worth sharing Marc

Marc Weber
have in a much better way such as installing arbitrary software packages. But I need to learn more about it before I do know how to proceed.
So at the moment I think I need another build tool but no longer another cross-platform packaging tool.
I'd like to share my work but I'm not sure wether its worth sharing
Marc
Thanks for the quick reply. I think the nix system is a pretty good system. I will try it out further. Thanks for the info. Ashish
participants (9)
-
Ashish Hanwadikar
-
Bryan O'Sullivan
-
Conal Elliott
-
Henning Thielemann
-
Ian Lynagh
-
Isaac Jones
-
Marc Weber
-
Neil Mitchell
-
Simon Marlow