hspec-tables-0.0.1: Table-driven (by-example) HSpec tests
Copyright(c) 2020 Marcin Rzeźnicki
LicenseMIT
MaintainerMarcin Rzeźnicki <marcin.rzeznicki@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Test.Hspec.Tables

Description

Table-driven (by-example) HSpec tests.

Example usage:

describe "multiplication table" $
 byExample
   ("x", "y", "result")
   [ (0, 0, 0),
     (0, 1, 0),
     (0, 2, 0),
     (1, 0, 0),
     (1, 1, 1),
     (1, 2, 2),
     (2, 0, 0),
     (2, 1, 2),
     (2, 2, 4)
   ]
   (\a b expected -> a * b == expected)
describe "reverse" $
 byExample
   ("list", "reversed")
   [("abc", "cba"), ("", ""), ("0123456", "6543210")]
   (shouldBe . reverse)
Synopsis

Documentation

class Table r where Source #

A type class for tables.

A table type binds together the row type r with the type of its header and the "generic" curried function forall p. r -> p

Minimal complete definition

apply

Associated Types

type Header r Source #

type Forall r p Source #

Methods

apply :: Forall r p -> r -> p Source #

showHeader :: Header r -> String Source #

default showHeader :: Show (Header r) => Header r -> String Source #

Instances

Instances details
Table (a, b) Source # 
Instance details

Defined in Test.Hspec.Tables

Associated Types

type Header (a, b) Source #

type Forall (a, b) p Source #

Methods

apply :: Forall (a, b) p -> (a, b) -> p Source #

showHeader :: Header (a, b) -> String Source #

Table (a, b, c) Source # 
Instance details

Defined in Test.Hspec.Tables

Associated Types

type Header (a, b, c) Source #

type Forall (a, b, c) p Source #

Methods

apply :: Forall (a, b, c) p -> (a, b, c) -> p Source #

showHeader :: Header (a, b, c) -> String Source #

Table (a, b, c, d) Source # 
Instance details

Defined in Test.Hspec.Tables

Associated Types

type Header (a, b, c, d) Source #

type Forall (a, b, c, d) p Source #

Methods

apply :: Forall (a, b, c, d) p -> (a, b, c, d) -> p Source #

showHeader :: Header (a, b, c, d) -> String Source #

Table (a, b, c, d, e) Source # 
Instance details

Defined in Test.Hspec.Tables

Associated Types

type Header (a, b, c, d, e) Source #

type Forall (a, b, c, d, e) p Source #

Methods

apply :: Forall (a, b, c, d, e) p -> (a, b, c, d, e) -> p Source #

showHeader :: Header (a, b, c, d, e) -> String Source #

Table (a, b, c, d, e, f) Source # 
Instance details

Defined in Test.Hspec.Tables

Associated Types

type Header (a, b, c, d, e, f) Source #

type Forall (a, b, c, d, e, f) p Source #

Methods

apply :: Forall (a, b, c, d, e, f) p -> (a, b, c, d, e, f) -> p Source #

showHeader :: Header (a, b, c, d, e, f) -> String Source #

Table (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Test.Hspec.Tables

Associated Types

type Header (a, b, c, d, e, f, g) Source #

type Forall (a, b, c, d, e, f, g) p Source #

Methods

apply :: Forall (a, b, c, d, e, f, g) p -> (a, b, c, d, e, f, g) -> p Source #

showHeader :: Header (a, b, c, d, e, f, g) -> String Source #

byExample Source #

Arguments

:: forall a r. (Table r, Example a, Show r) 
=> Header r

header - tuple of strings (max 7 for now); used to describe this spec, its arity == number of columns

-> [r]

rows - list of tuples of examples; arity of each tuple must match the number of columns (== arity of the header)

-> Forall r a

assertion - curried function from a row to an a - if row type is (b,c,d) then it must be (Example a) => b -> c -> d -> a

-> SpecWith (Arg a) 

Creates a Spec from the table consisting of:

  • header
  • list of examples (rows)
  • assertion

The resulting spec consists of one test per each row. For example:

byExample
  ("list", "reversed")
  [("abc", "cba"), ("", ""), ("0123456", "6543210")]
 (shouldBe . reverse)

is equivalent to:

describe (show ("list", "reversed")) $ do
  specify (show ("abc", "cba")) $ reverse "abc" `shouldBe` "cba"
  specify (show ("", "")) $ reverse "" `shouldBe` ""
  specify (show ("0123456", "6543210")) $ reverse "0123456" `shouldBe` "6543210"

testTable :: forall a r. (Table r, Example a, Show r) => Header r -> [r] -> Forall r a -> SpecWith (Arg a) Source #

Alias for byExample