tasty-hspec-0.1: Hspec support for the Tasty test framework.

Safe HaskellNone

Test.Tasty.Hspec

Contents

Synopsis

Documentation

testCase :: TestName -> Spec -> TestTreeSource

Turn an hspec Spec into a tasty TestTree.

 module AnimalsSpec (tests) where

 import Test.Tasty.Hspec

 tests :: TestTree
 tests = testGroup "animals"
     [ testCase "mammals" mammalsSpec
     , testCase "birds"   birdsSpec
     ]

 mammalsSpec :: Spec
 mammalsSpec = do
     describe "cow" $ do
         it "moos" $
             speak cow `shouldBe` "moo"

         it "eats grass" $
             hungryFor cow `shouldBe` "grass"

 birdsSpec :: Spec
 birdsSpec = do
     describe "ostrich" $ do
         it "sticks its head in sand" $
             fmap (`shouldBe` InSand) getHeadState

Re-exports

module Test.Hspec

type TestName = String

The name of a test or a group of tests

data TestTree

The main data structure defining a test suite.

It consists of individual test cases and properties, organized in named groups which form a tree-like hierarchy.

There is no generic way to create a test case. Instead, every test provider (tasty-hunit, tasty-smallcheck etc.) provides a function to turn a test case into a TestTree.

Groups can be created using testGroup.