cabal test and detailed-0.9 strangeness
Daniel Peebles
pumpkingod at gmail.com
Sun Jan 9 22:53:32 CET 2011
Hi,
I've been playing with the detailed-0.9 test-suite option on a package of
mine. First, what I have:
in my package root, I have my .cabal file and a tests folder containing a
Tests.hs
in my Tests.hs, I took the code from the online user guide (minus the odd
guards with == True and == False):
{-# LANGUAGE FlexibleInstances #-}
module Tests ( tests ) where
import Distribution.TestSuite
instance TestOptions (String, Bool) where
name = fst
options = const []
defaultOptions _ = return (Options [])
check _ _ = []
instance PureTestable (String, Bool) where
run (name, True) _ = Pass
run (name, False) _ = Fail (name ++ " failed!")
test :: (String, Bool) -> Test
test = pure
-- In actual usage, the instances 'TestOptions (String, Bool)' and
-- 'PureTestable (String, Bool)', as well as the function 'test', would be
-- provided by the test framework.
tests :: [Test]
tests =
[ test ("bar-1", True)
, test ("bar-2", False)
]
in my .cabal file:
Test-Suite binutils
Hs-source-dirs: tests/
Type: detailed-0.9
Test-module: Tests
Build-depends: base, Cabal >= 1.9.2
I then run cabal configure --enable-tests and finally run cabal test.
It gives me this:
Running 1 test suites...
Test suite binutils: RUNNING...
Test suite binutils: PASS
Test suite logged to: dist/test/charm-0.0.1-binutils.log
1 of 1 test suites (0 of 0 test cases) passed.
Which seems odd, since there are 2 test cases (not 0 as the output claims)
and one of them should definitely be failing (it has a False in it).
Am I doing something wrong?
Thanks,
Daniel
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/cabal-devel/attachments/20110109/efbddc75/attachment.htm>
More information about the cabal-devel
mailing list