[Haskell-cafe] Re: ANNOUNCE: Coadjute 0.0.1, generic build tool
Matti Niemenmaa
matti.niemenmaa+news at iki.fi
Sun Jan 18 13:47:46 EST 2009
Henning Thielemann wrote:
> Matti Niemenmaa schrieb:
>> Announcing the release of Coadjute, version 0.0.1!
>>
>> Web site: http://iki.fi/matti.niemenmaa/coadjute/
>> Hackage:
>> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Coadjute
<snip>
> How does it compare to
> http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hake
Short answer: the question that comes to mind is "how does hake compare
to make?" Coadjute seems to be more capable, in general, but then I
don't know pretty much anything about hake.
Somewhat longer answer:
Coadjute is better in that:
1. hake's documentation is rather sparse. I have no idea what most
functions do, or even what exactly the main program does.
2. hake doesn't seem to do parallel builds, but I'm not sure because
of point 1.
3. Coadjute keeps track of command line arguments (see docs for
details): for me this is really a killer feature, I don't know of
anything else which does this.
4. hake always uses timestamps, Coadjute can use MD5 hashes as well.
5. Coadjute can have arbitrary path specifications, hake's rules seem
to be based on file extensions only, thus applying only to the
current directory. Peter Miller's "Recursive Make Considered
Harmful" comes to mind: http://miller.emu.id.au/pmiller/books/rmch/
hake is better in that:
1. Its syntax is more concise.
2. It looks like it'd be easier to pick up for make users.
3. It seems to have some built-in support for more complex operations
than Coadjute, e.g. the 'ruleSS' function. (Coadjute can still do
this, just not as concisely. See point 1.)
With the disclaimer that all I know about hake comes from its Hackage
page and home page, which don't really tell me very much. I can't get
any information out of the hake binary either: it doesn't respond to
--help or similar.
Much longer answer:
I figured I'd convert the example there to Coadjute and see what
happens. Result, with some inline comments:
----
import Coadjute
import System.FilePath (replaceExtension)
import System.FilePath.Glob (globDir, compile)
import System.Process (rawSystem)
main = do
-- assuming that hake's rules apply to the current directory only...
([sfx1, sfx2, c, cc, foo],_) <-
globDir (map compile ["*.sfx1","*.sfx2","*.c","*.cc","foo*"]) "."
coadjute $ do
-- Coadjute doesn't offer arbitrary source/target pairing
-- currently: it wants you to derive your targets from your
-- sources somehow instead of just specifying them directly
ruleM' "greeting"
(\_ _ -> run "linker"
["-o","greeting","hello.o","good-bye.o"])
(sourceToDatum (\_ -> ( ["good-bye.o"]
, ["greeting","greeting.log"]
))
["hello.o"])
rule' ".sfx1 to .o" (buildO "compiler1")
(sourceToDatum' (chExt "o") sfx1)
rule' ".sfx2 to .o" (buildO "compiler2")
(sourceToDatum' (chExt "o") sfx2)
-- Things like "make clean" don't really map well to Coadjute
-- currently...
--
-- Not only can it not be specified nicely, but the rule is always
-- applied unless we have it create some kind of dummy file
rule' "clean"
(\_ _ -> do run "rm" ["-f", "hello.o", "good-bye.o"
, "greeting", "greeting.log"]
run "touch" ["DUMMY"])
(sourceToDatum' (const "DUMMY") [""])
rule' ".c to .o"
(\(s:_) _ -> run "gcc" ["-c", s])
(sourceToDatum' (chExt "o") c)
rule' ".cc to .o"
(\(s:_) _ -> run "g++" ["-c", s])
(sourceToDatum' (chExt "O") cc)
-- No equivalent to hake's ruleSS: deal with C/C++ dichotomy
-- yourself
rule' "C++ .o to binaries" (buildO "g++")
(sourceToDatum' (chExt "") $ map (chExt "o") cc)
rule' "C .o to binaries" (buildO "gcc")
(sourceToDatum' (chExt "") $ map (chExt "o") c)
ruleM' "Not sure what this is"
(\[s] (t:_) -> do
gen <- readFile s
writeFile t $ unlines $
[ "#!/bin/sh", "echo This is script" ] ++ lines gen)
(sourceToDatum'
(\s -> [replaceExtension s "gen", "Hakefile"])
foo)
where chExt = flip replaceExtension
run cmd args = rawSystem cmd args >> return ()
buildO compiler [s] t = run compiler [s,"-o",t]
----
I really don't know what that last rule (the one generated with the
'base' function in hake) is supposed to do. With no documentation I have
absolutely no idea: my conversion above is my best guess, but I doubt I
got it right.
In any case, seems there are some things which hake's interface can do
that Coadjute's can't:
1. Arbitrary source/target pairing. This was really a "d'oh" moment
for me and is trivial to fix. I think I'll even remove the current
sourceToDatum functions and just provide a primitive with which you
can map, fold, whatever.
2. Rules which have no targets. Currently these can't work since I
haven't yet implemented being able to choose which rules to apply:
Coadjute just always runs them all. But this is definitely
something on my agenda.
Although I've also been thinking about alternative avenues: the
main use case for these is probably the 'make clean' type of
action, which I, at least, use mainly to bypass the problem that
Coadjute's argument tracking already solves: wanting to rebuild
with different flags passed to the compiler (or equivalent).
And you can of course deal with this by simply doing it in the main
function, but outside the Coadjute monad:
when ("clean" `elem` userArgs) $ rawSystem "rm" ["-f", ...]
Which is one reason why I'm not sure if it's necessary at all.
3. The ruleSS thing: being able to choose a build action based on what
rule caused this rule to be built. Looks interesting, but I'm not
sure how useful it is in practice, nor how it should be implemented
in Coadjute.
Another thing that seems clear is that Coadjute is more primitive. hake
contains around 40 functions; Coadjute boils down to five, with three
convenience functions. And from point 1 above, I'm thinking of removing
two, leaving the counts at four and two.
Originally I did intend for Coadjute to also offer all kinds of utility
functions that could be useful in Adjutant files, but at some point I
figured that it's better to provide a minimal, clean, extensible
interface and leave the rest to libraries. My Pipe and Glob libraries
began their lives as modules in Coadjute.Util.
hake seems to provide alternatives by having functions with the same
name in different modules: FunSetRaw is for raw commands, FunSetIO for
arbitrary IO expressions. Coadjute provides only the latter and
discourages the former as a design philosophy—we have Haskell: you
should be able to do a lot more than what plain make can without having
to call other programs, and you should try hard to avoid doing so.
(Platform-agnostic programs with complicated, platform-specific build
systems tick me off.)
Anyway, hake looks interesting but it's not a replacement for Coadjute;
and neither is Coadjute for hake. To be completely honest I'm not sure
what use case hake is meant to solve: how does it improve over plain make?
More information about the Haskell-Cafe
mailing list