Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Test.Microspec
Description
Tests can be structured as nested it
/ describe
statements
E.g.
microspec $ do describe "plus" $ do it "adds positive numbers" $ do it "does 1 + 1" $ 1 + 1 === 2 it "does 2 + 2" $ 2 + 2 === 4 it "is commutative" $ \x y -> x + y === y + (x :: Int)
...which will return, nicely in green instead of bold:
plus adds positive numbers does 1 + 1 does 2 + 2 is commutative ----- Successes: 3, Pending: 0, Failures: 0
Synopsis
- microspec :: Microspec () -> IO ()
- microspecWith :: MArgs -> Microspec () -> IO ()
- describe :: MTestable t => String -> t -> Microspec ()
- it :: MTestable t => String -> t -> Microspec ()
- pending :: Pending
- prop :: MTestable prop => String -> prop -> Microspec ()
- data Microspec a
- class MTestable t
- data MArgs = MArgs {}
- defaultMArgs :: MArgs
- shouldBe :: (Eq x, Show x) => x -> x -> Property
- module Test.QuickCheck
- module Test.QuickCheck
- module Test.QuickCheck.Modifiers
- module Test.QuickCheck.Monadic
Specification
microspec :: Microspec () -> IO () Source #
Run your spec. Put this at the top level, e.g.:
main = microspec $ do describe "plus 1" $ 3 + 1 === 4
describe :: MTestable t => String -> t -> Microspec () Source #
Describe a test, e.g.:
describe "reverse 'foo' is 'oof'" $ reverse "foo" === "oof"
prop :: MTestable prop => String -> prop -> Microspec () Source #
Note that you don't need to use this to create a test, e.g.:
describe "reverse preserves length" $ \l -> length (reverse l) === length l
A series of tests, to run with microspec
Something which can be tested
Note both Bools and Properties can be tested, but only Properties show the values that weren't equal
For both unit tests and property tests, if you want to see the outputs
of failed tests use ===
. If you just want to test for
equality, use ==
.
For example, the outputs of running:
microspec $ do describe "baddies" $ do it "isn't 1 ==" $ 0 == (1 :: Int) it "isn't 1 ===" $ 0 === (1 :: Int) it "isn't always 1 ==" $ x -> x == (1 :: Int) it "isn't always 1 ===" $ x -> x === (1 :: Int)
are:
isn't 1 == - *** Failed! Falsifiable (after 1 test) isn't 1 === - *** Failed! Falsifiable (after 1 test): | 0 /= 1 isn't always 1 == - *** Failed! Falsifiable (after 1 test): | 0 isn't always 1 === - *** Failed! Falsifiable (after 1 test): | 0 | 0 /= 1
Minimal complete definition
Configuration
Tweak how tests are run, with microspecWith
.
Constructors
MArgs | |
Fields
|
defaultMArgs :: MArgs Source #
Default arguments. Calling "microspec" is the same as calling "microspecWith defaultMArgs".
Compatibility
shouldBe :: (Eq x, Show x) => x -> x -> Property Source #
Hspec compatibility. Equivalent to using ===
module Test.QuickCheck
module Test.QuickCheck
module Test.QuickCheck.Modifiers
module Test.QuickCheck.Monadic