Skip to content

Instantly share code, notes, and snippets.

@naoto-ogawa
Created November 12, 2017 07:16
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save naoto-ogawa/e4d9965083bf6ce7daf8544b5a15edf8 to your computer and use it in GitHub Desktop.
Save naoto-ogawa/e4d9965083bf6ce7daf8544b5a15edf8 to your computer and use it in GitHub Desktop.
A test comparison between Hunit and Hspec.
module Main where
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.Hspec
main :: IO ()
main = do
hspec01 <- spec01 -- spec01 :: IO TestTree -> IO monad
let hunit01 = test01 -- test01 -> pure
defaultMain $ testGroup "A test comparison between Hunit and Hspec." [hunit01, hspec01]
-- HUnit Bridge
test01 :: TestTree
test01 = testCase "my_hunit_01" $ -- testCase :: TestName -> Assertion -> TestTree
assertEqual "1+2=2 ?" myTest 2 -- assertEqual :: (Show a, Eq a) => String -> a -> a -> Assertion
-- HSpec Bridge
spec01 :: IO TestTree
spec01 = testSpec "my_hspec_01" $ -- testSpec :: TestName -> Spec -> IO TestTree
it "1+2=2 ?" $ -- it :: (HasCallStack, Example a) => String -> a -> SpecWith (Arg a)
myTest `shouldBe` 2 -- shouldBe :: (Show a, Eq a) => a -> a -> Expectation
myTest :: Int
myTest = 1 + 2
{-
assertXXXX = it + shouldXXXX
> :t assert
assert assertBool assertEqual assertFailure assertString assertionPredicate
> :t should
shouldBe shouldEndWith shouldNotBe shouldNotReturn shouldReturn shouldStartWith
shouldContain shouldMatchList shouldNotContain shouldNotSatisfy shouldSatisfy shouldThrow
-}
-- >>> :l test/MyTest03.hs
-- [1 of 1] Compiling Main ( test/MyTest03.hs, interpreted )
-- Ok, modules loaded: Main.
-- >>> main
-- A test comparison between Hunit and Hspec.
-- my_hunit_01: FAIL
-- 1+2=2 ?
-- expected: 3
-- but got: 2
-- my_hspec_01
-- 1+2=2 ?: FAIL
-- expected 2, but got 3
--
-- 2 out of 2 tests failed (0.00s)
-- *** Exception: ExitFailure 1
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment