[Haskell-cafe] GSoC: Improving Cabal's Test Support

Thomas Tuegel ttuegel at gmail.com
Thu Apr 1 18:52:44 EDT 2010


Hello community!

I've been working on a proposal for Google Summer of Code 2010 to work
on improving Cabal's test support, as described on the Haskell SoC
Trac [1].  Today I'm looking for feedback to see if what I intend is
what people want/need.  As you read this, I kindly ask that you
consider: 1) Would you use the facility I describe, were it available?
and 2) What additional features would you like to see?

There have been two separate suggestions (of which I am aware) of ways
to integrate tests into Cabal.  One is to build the tests into their
own executable which uses an error code on exit to indicate test
failure.  The second is to have package authors write modules which
Cabal will load (dynamically?) and run the tests from.  The former
method has the advantage of being simpler to implement, but is
probably too granular.  Although the second suggestion avoids some
security concerns, it seems to me that a malicious party could simply
put nefarious code into their Setup.hs file anyway, or even in the
library being tested.

I propose to build a test suite as its own executable, but to avoid
the problem of granularity by producing an output file detailing the
success or failure of individual tests and any relevant error
messages.  The format of the file would be standardized through
library routines I propose to write; these routines would run tests
with HUnit or QuickCheck and process them into a common format.
Cabal, or any other utility, could read this file to determine the
state of the test suite.  Perhaps Cabal could even warn the user about
installing packages with failing tests.

Under this proposal, a test suite would look something like this
(suppose I am writing a test suite for a module Foo, which has an
existing test suite in QuickCheck):

> module Main where
>
> import Foo
> import Test.QuickCheck
> import Distribution.Test -- This module is part of the project I propose
>
> main = runTests
>   [ ("testBar", wrap $ testBar), ("testBaz", wrap $ testBaz) ] -- (name, test)

'runTests' and 'wrap' would be provided by 'Distribution.Test'.
'wrap' would standardize the output of test routines.  For QuickCheck
tests, it would probably look like:

> wrap :: Testable a => a -> IO (Bool, String)

where the Bool indicates success and the String can be an error
message the test produced.  'runTests' would take the list of tests,
format their results, and write the output to a file:

> runTests :: [(String, IO (Bool, String))] -> IO ()

I would probably gather the test results into a value of type
'[(String, Bool, String)]' -- the name, status, and messages
associated with each test -- and use 'show' to produce a nice,
human-readable, machine-parsable file.

The test suite would be included in the package description file with
a stanza such as:

> Test
>         main-is: Test.hs
>         build-depends: foo, QuickCheck, Cabal

This would take all the same options as an 'Executable' stanza, but
would tell Cabal to run this executable when './Setup test' is
invoked.  This of course requires Cabal to support building
executables that depend on the library in the same package.  Since
version 1.8, Cabal supposedly supports this, but my experiments
indicate the support is a little broken. (GHC is invoked with the
'-package-id' option, but Cabal only gives it the package name.
Fixing this would naturally be on the agenda for this project.)

At this point, the package author need only run:

$ ./Setup configure
$ ./Setup build
$ ./Setup test

to produce a file detailing the results of the test suite.

I apologize for taking up your time with a such a lengthy message, and
eagerly await your feedback!

Thanks!
-- 
Thomas Tuegel

[1]  http://hackage.haskell.org/trac/summer-of-code/ticket/1581


More information about the Haskell-Cafe mailing list