sydtest-0.11.0.2: A modern testing framework for Haskell with good defaults and advanced testing features.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Syd.Def.Specify

Description

This module defines all the functions you will use to define your test suite.

Synopsis

API Functions

Declaring tests

describe Source #

Arguments

:: String

The test group description

-> TestDefM outers inner () 
-> TestDefM outers inner () 

Declare a test group

Example usage:

describe "addition" $ do
    it "adds 3 to 5 to result in 8" $
        3 + 5 `shouldBe` 8
    it "adds 4 to 7 to result in 11" $
        4 + 7 `shouldBe` 11

it Source #

Arguments

:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) 
=> String

The description of the test

-> test

The test itself

-> TestDefM outers inner () 

Declare a test

Note: Don't look at the type signature unless you really have to, just follow the examples.

Example usage:

Tests without resources

Pure test
describe "addition" $
    it "adds 3 to 5 to result in 8" $
        3 + 5 == 8
IO test
describe "readFile and writeFile" $
    it "reads back what it wrote for this example" $ do
        let cts = "hello world"
        let fp = "test.txt"
        writeFile fp cts
        cts' <- readFile fp
        cts' `shouldBe` cts
Pure Property test
describe "sort" $
    it "is idempotent" $
        forAllValid $ \ls ->
            sort (sort ls) `shouldBe` (sort (ls :: [Int]))
IO Property test
describe "readFile and writeFile" $
    it "reads back what it wrote for any example" $ do
        forAllValid $ \fp ->
            forAllValid $ \cts -> do
                writeFile fp cts
                cts' <- readFile fp
                cts' `shouldBe` cts

Tests with an inner resource

Pure test

This is quite a rare use-case but here is an example anyway:

before (pure 3) $ describe "addition" $
    it "adds 3 to 5 to result in 8" $ \i ->
        i + 5 == 8
IO test

This test sets up a temporary directory as an inner resource, and makes it available to each test in the group below.

let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir
in around setUpTempDir describe "readFile and writeFile" $
    it "reads back what it wrote for this example" $ \tempDir -> do
        let cts = "hello world"
        let fp = tempDir </> "test.txt"
        writeFile fp cts
        cts' <- readFile fp
        cts' `shouldBe` cts
Pure property test

This is quite a rare use-case but here is an example anyway:

before (pure 3) $ describe "multiplication" $
    it "is commutative for 5" $ \i ->
        i * 5 == 5 * 3
IO property test
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir
in around setUpTempDir describe "readFile and writeFile" $
    it "reads back what it wrote for this example" $ \tempDir ->
        property $ \cts -> do
            let fp = tempDir </> "test.txt"
            writeFile fp cts
            cts' <- readFile fp
            cts' `shouldBe` cts

itWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

Declare a test that uses an outer resource

Example usage:

Tests with an outer resource

Pure test
Expand

This is quite a rare use-case but here is an example anyway:

beforeAll (pure 3) $ describe "addition" $
    itWithOuter "adds 3 to 5 to result in 8" $ \i ->
        i + 5 == 8
IO test

This test sets up a temporary directory as an inner resource, and makes it available to each test in the group below.

let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir
in aroundAll setUpTempDir describe "readFile and writeFile" $
    itWithOuter "reads back what it wrote for this example" $ \tempDir -> do
        let cts = "hello world"
        let fp = tempDir </> "test.txt"
        writeFile fp cts
        cts' <- readFile fp
        cts' `shouldBe` cts
Pure property test
Expand

This is quite a rare use-case but here is an example anyway:

beforeAll (pure 3) $ describe "multiplication" $
    itWithOuter "is commutative for 5" $ \i ->
        i * 5 == 5 * 3
IO property test
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir
in aroundAll setUpTempDir describe "readFile and writeFile" $
    itWithouter "reads back what it wrote for this example" $ \tempDir ->
        property $ \cts -> do
            let fp = tempDir </> "test.txt"
            writeFile fp cts
            cts' <- readFile fp
            cts' `shouldBe` cts

itWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

Declare a test that uses both an inner and an outer resource

Example usage:

Tests with both an inner and an outer resource

Pure test
Expand

This is quite a rare use-case but here is an example anyway:

beforeAll (pure 3) $ before (pure 5) $ describe "addition" $
    itWithBoth "adds 3 to 5 to result in 8" $ \i j ->
        i + j == 8
IO test

This test sets up a temporary directory as an inner resource, and makes it available to each test in the group below.

let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir
in aroundAll setUpTempDir describe "readFile and writeFile" $ before (pure "hello world") $
    itWithBoth "reads back what it wrote for this example" $ \tempDir cts -> do
        let fp = tempDir </> "test.txt"
        writeFile fp cts
        cts' <- readFile fp
        cts' `shouldBe` cts
Pure property test
Expand

This is quite a rare use-case but here is an example anyway:

beforeAll (pure 3) $ before (pure 5) $ describe "multiplication" $
    itWithBoth "is commutative" $ \i j ->
        i * j == 5 * 3
IO property test
let setUpTempDir func = withSystemTempDir $ \tempDir -> func tempDir
in aroundAll setUpTempDir describe "readFile and writeFile" $ before (pure "test.txt") $
    itWithBoth "reads back what it wrote for this example" $ \tempDir fileName ->
        property $ \cts -> do
            let fp = tempDir </> fileName
            writeFile fp cts
            cts' <- readFile fp
            cts' `shouldBe` cts

itWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #

Declare a test that uses all outer resources

You will most likely never need this function, but in case you do: Note that this will always require a type annotation, along with the GADTs and ScopedTypeVariables extensions.

Example usage

beforeAll (pure 'a') $ beforeAll (pure 5) $
    itWithAll "example" $
        \(HCons c (HCons i HNil) :: HList '[Char, Int]) () ->
            (c, i) `shouldeBe` ('a', 5)

specify Source #

Arguments

:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) 
=> String

The description of the test

-> test

The test itself

-> TestDefM outers inner () 

A synonym for it

specifyWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

A synonym for itWithOuter

specifyWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

A synonym for itWithBoth

specifyWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #

A synonym for itWithAll

prop :: Testable prop => String -> prop -> Spec Source #

Convenience function for backwards compatibility with hspec

prop s p = it s $ property p

Declaring commented-out tests

xdescribe :: String -> TestDefM outers inner () -> TestDefM outers inner () Source #

xit Source #

Arguments

:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) 
=> String

The description of the test

-> test

The test itself

-> TestDefM outers inner () 

xitWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

xitWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

xitWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #

xspecify Source #

Arguments

:: forall outers inner test. (HasCallStack, IsTest test, Arg1 test ~ (), Arg2 test ~ inner) 
=> String

The description of the test

-> test

The test itself

-> TestDefM outers inner () 

A synonym for xit

xspecifyWithOuter :: (HasCallStack, IsTest test, Arg1 test ~ inner, Arg2 test ~ outer) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

A synonym for xitWithOuter

xspecifyWithBoth :: (HasCallStack, IsTest test, Arg1 test ~ outer, Arg2 test ~ inner) => String -> test -> TestDefM (outer ': otherOuters) inner () Source #

A synonym for xitWithBoth

xspecifyWithAll :: (HasCallStack, IsTest test, Arg1 test ~ HList outers, Arg2 test ~ inner) => String -> test -> TestDefM outers inner () Source #

A synonym for xitWithAll

Pending tests

pending :: String -> TestDefM outers inner () Source #

Declare a test that has not been written yet.

pendingWith :: String -> String -> TestDefM outers inner () Source #

Declare a test that has not been written yet for the given reason.