Any remaining test patches?

Duncan Coutts duncan.coutts at googlemail.com
Sat May 21 16:20:36 CEST 2011


On 18 May 2011 15:01, Thomas Tuegel <ttuegel at gmail.com> wrote:
> On Wed, May 18, 2011 at 4:34 AM, Johan Tibell <johan.tibell at gmail.com> wrote:
>> Sorry for having to leave so abruptly yesterday. Could someone please
>> summarize the discussion? Are we going with GetOpt?
>
> We didn't reach a decision; primarily, I think, because I had to leave
> before Duncan really had a chance to review the patch. (There really
> wasn't any discussion after you had to leave.) But, my understanding
> of the discussion before you left is that Duncan would prefer a custom
> solution, rather than GetOpt. (Duncan, please correct me if that isn't
> the case).

Ok, I've looked at the Distribution.TestSuite API and had a go at
designing something along the lines of what I was thinking. I'll try
and explain this design and compare three designs: Thomas's current
patch, my prototype and the the test-framework test interface.

So the design in the current patch is nice and short:

class Testable t where
    name :: t -> String
    options :: [OptDescr (t -> t)]
    defaultOptions :: t -> IO [String]
    run :: t -> IO Result

data Result
    = Pass
    | Fail  ErrorMessage
    | Error ErrorMessage
    deriving (Read, Show, Eq)

data Test = forall t. Testable t => Test t

The test suite will then expose a value of type [Test].

So the interesting aspects are:
 * the API uses a type class and an existential wrapper to hide the
specific type of each test.
 * the default options are obtained using IO
 * it uses GetOpt to accumulate key/value style string options into
the test instance, which can then be run
   (Presumably at least the default options must be added before the
test can be run.)

Here's the equivalent bit of my design (the TestResult is the same):

data TestInstance
   = TestInstance {
       run            :: IO TestResult
       name           :: String,

       concurrentSafe :: Bool,
       expectedFail   :: Bool,

       options        :: [OptionDescr]
       setOption      :: String -> String -> Either String TestInstance
     }

Minor difference: extra flags for indicating whether the test is safe
for concurrent execution (e.g. if it's pure or has only local side
effects) and whether the test case is in fact expected to fail (so
numbers of expected vs unexpected failures can be reported).

The first major difference is that we do the "OO" bit differently.
Instead of using a type class and an existential wrapper, we use a
record. These two styles are pretty similar but the record avoids the
use of existential types. Since the test agents using this interface
never know or need to know the actual type of the test (they will
always use Test above and manipulate it via the type class interface)
then there is no advantage to using a type class.

The option setting is rather similar in both designs. In both you end
up using a function of type String -> String -> Test -> Test to
accumulate a key/value option pair into the test instance. This lets
the user add any number of options before running the test. The slight
difference in style is down to the different OO encoding (class based
vs record based).

The major difference with the options is of course how they are
validated and described (which I have not yet detailed). GetOpt does
not actually provide any validation of options, that is, for an option
--foo=bar, there is no parsing/validation of the string "bar". GetOpt
just parses the overall command line string ["--foo=bar", ...]. This
setOption function gives the possibility of validating the value
string and producing an error message.

Note that I don't have an IO action to get any default options. In
this design it must always be possible to run the test with no options
supplied. Internally, if a test does need some options specified then
it just has to fill them in with its internal defaults.

So, all the options are just (String, String) key value pairs and we
can validate them. Obviously we also need some discoverability of what
options are available and some information to construct a sensible
user interface (either command line, config file, web UI or IDE GUI).

data OptionDescr
   = OptionDescr {
       optionName        :: String,
       optionDescription :: String,
       optionType        :: OptionType,
       optionDefault    :: Maybe String
     }

The name and description are much like in GetOpt. The optional default
is purely informative, for user interfaces that are able to display
defaults (eg a web form). The OptionType is to give a user interface
some extra info on what is expected so that they can present an
appropriate interface and do some up front validation. Of course the
real validation is done via setOption, or for things that can only
really be validated by doing IO (like reading files) then they have to
be deferred to when the test is actually run.

So this list is just informative:

data OptionType
   = OptionFile {
       optionFileMustExist  :: Bool,
       optionFileIsDir      :: Bool,
       optionFileExtensions :: [String]
     }
   | OptionString {
       optionStringMultiline :: Bool
     }
   | OptionNumber {
       optionNumberIsInt   :: Bool,
       optionNumberBounds  :: (Maybe String, Maybe String)
     }
   | OptionBool
   | OptionEnum  [String]
   | OptionSet   [String]
   | OptionRngSeed

You can imagine how each of these could be used as hints to make a
more helpful web form or GUI interface. They could also let a command
line ui do some up front validation too.

The most general case is OptionString for when no more specific
alternative is appropriate.


Now, I also looked again at what test-framework does and it has some
interesting things and some things that are unnecessary for our
purposes. There are two things there that I think we should consider.
The first is the grouping of tests into a related bundles, or in
general a hierarchy:

data Test = forall i r t. Testlike i r t => Test TestName t
          | TestGroup TestName [Test]
          | PlusTestOptions TestOptions Test

So we either have a individual test or a group of tests (which
themselves can contain groups etc). I'm sure this is nice for
displaying in a UI what tests can be run and displaying results of a
run. Imagine an interactive UI that lets the user select a group of
tests to be run, or an html report showing results by group.

We could do something like this:

data Tests = Test TestInstance
           | TestGroup TestName [Tests]

The PlusTestOptions is interesting. As I understand this, it is really
from the point of view of the author of the test suite: they are
providing additional default test options for this test or group of
tests. I don't think this is necessary from the point of view of the
test agent, they do not need to know this. The above could be lifted
into a structure without PlusTestOptions simply by pre-applying the
test options to that subtree.

On the other hand, perhaps it is useful for an agent presenting a user
interface to be able to know that a whole group of test all take the
same set of options. So perhaps we should have:

data Tests = Test TestInstance
           | TestGroup TestName [Tests]
           | ExtraTestOptions [OptionDescr] Tests

So this means that all of the tests below this ExtraTestOptions take
the given set of options. Then individual tests would usually have an
empty options set, or perhaps just add one or two for that special
case. This grouping of test options should enable better user
interfaces.

Another interesting part of test-framework is what you get when you run a test:

runTest :: t -> IO (i :~> r, IO ())

So I the main point here is that it gives us progress / logging while
the test is being run. The i :~> r thing is basically just a lazy list
with values of type i spat out along the way and finally ending in a
result of type r.

The way it's done in test-framework is to have a pure i :~> r lazy
list and a separate IO () action that does the real work. The IO
action performs the test and pokes the results into a Concurrent.Chan.
The i :~> r lazy list is extracted from the Chan using
getChanContents.

Honestly, I don't know why Max did it this way, seems to me a much
more direct approach is:

data TestProgress
    = Finished TestResult
    | Progress String (IO TestProgress)

So it's not a lazy list, it's a list with explicit IO to get the tail.
The test-framework approach could be lifted into this fairly easily I
think.

Note that this kind of progress reporting is actually quite important.
You cannot have each test logging information to stdout if you're
going to run any tests concurrently. But it is quite nice to see
progress (e.g. from QuickCheck) for the tests that are currently
running, which is exactly what test-framework does using a 'top' like
console interface (you can imagine GUI ones too).

Comments, thoughts on any/all of this appreciated.

Duncan



More information about the cabal-devel mailing list