tasty-auto: Simple auto discovery for Tasty

[ deprecated, library, mit, program, testing ] [ Propose Tags ]
Deprecated in favor of tasty-discover

Simple auto discovery for Tasty


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.0.0.0, 0.1.0.0, 0.1.0.1, 0.1.0.2, 0.2.0.0
Dependencies base (>=4.8 && <5), directory (>=1.1 && <1.3), filepath (>=1.3 && <1.5), tasty-auto [details]
License MIT
Copyright 2017 Daniel Mendler
Author Daniel Mendler <mail@daniel-mendler.de>
Maintainer Daniel Mendler <mail@daniel-mendler.de>
Category Testing
Home page https://github.com/minad/tasty-auto#readme
Bug tracker https://github.com/minad/tasty-auto/issues
Source repo head: git clone https://github.com/minad/tasty-auto
Uploaded by minad at 2017-01-24T03:12:58Z
Distributions
Executables tasty-auto
Downloads 3029 total (13 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2017-01-24 [all 1 reports]

Readme for tasty-auto-0.0.0.0

[back to package description]

tasty-auto: Simple auto discovery for Tasty

Hackage Build Status

This package provides auto discovery for the tasty test framework.

  • Install tasty-auto (using cabal or stack)

  • Create a file test/test.hs

-- test/test.hs
{-# OPTIONS_GHC -F -pgmF tasty-auto #-}
  • Put your tests in files with the suffix *Test.hs or *Spec.hs. Functions with the following prefixes are automatically discovered:

  • prop_ for QuickCheck properties

  • scprop_ for SmallCheck properties

  • case_ for HUnit test cases (overloaded for IO (), IO String and (String -> IO ()) -> IO)

  • spec_ for Hspec specifications

  • test_ for Tasty TestTrees (overloaded for TestTree, [TestTree], IO TestTree and IO [TestTree])

Examples

-- test/PropTest.hs
module PropTest where

prop_Addition_is_commutative :: Int -> Int -> Bool
prop_Addition_is_commutative a b = a + b == b + a
-- test/CaseTest.hs
module CaseTest where

import Test.Tasty.HUnit

case_List_comparison_with_different_length :: IO ()
case_List_comparison_with_different_length = [1, 2, 3] `compare` [1,2] @?= GT
-- test/TestSpec.hs
module TestSpec where

import Test.Tasty.Hspec

spec_Prelude :: Spec
spec_Prelude = do
  describe "Prelude.head" $ do
    it "returns the first element of a list" $ do
      head [23 ..] `shouldBe` (23 :: Int)
-- test/TreeTest.hs
{-# LANGUAGE ScopedTypeVariables #-}
module TreeTest where

import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Tasty.HUnit

test_Addition :: TestTree
test_Addition = testProperty "Addition commutes" $ \(a :: Int) (b :: Int) -> a + b == b + a

test_Multiplication :: [TestTree]
test_Multiplication =
  [ testProperty "Multiplication commutes" $ \(a :: Int) (b :: Int) -> a * b == b * a
  , testProperty "One is identity" $ \(a :: Int) -> a * 1 == a
  ]

test_Generate_Tree :: IO TestTree
test_Generate_Tree = do
  input <- pure "Some input"
  pure $ testCase input $ pure ()

test_Generate_Trees :: IO [TestTree]
test_Generate_Trees = do
  inputs <- pure ["First input", "Second input"]
  pure $ map (\s -> testCase s $ pure ()) inputs