-- |
-- maintainer: Simon Hengel <sol@typeful.net>
module Test.Hspec.Contrib.HUnit (
-- * Interoperability with HUnit
  fromHUnitTest
, specListFromHUnitTest
) where

import           Test.Hspec.Core.Spec
import           Test.HUnit (Test (..))

-- |
-- Convert a HUnit test suite to a spec.  This can be used to run existing
-- HUnit tests with Hspec.
fromHUnitTest :: Test -> Spec
fromHUnitTest :: Test -> Spec
fromHUnitTest = forall a. [SpecTree a] -> SpecWith a
fromSpecList forall b c a. (b -> c) -> (a -> b) -> a -> c
. Test -> [SpecTree ()]
specListFromHUnitTest

-- |
-- @specListFromHUnitTest@ is similar to `fromHUnitTest`, but it constructs a
-- list of `SpecTree`s instead of a `Spec`.
specListFromHUnitTest :: Test -> [SpecTree ()]
specListFromHUnitTest :: Test -> [SpecTree ()]
specListFromHUnitTest Test
t = case Test
t of
  TestList [Test]
xs -> forall a b. (a -> b) -> [a] -> [b]
map Test -> SpecTree ()
go [Test]
xs
  Test
x -> [Test -> SpecTree ()
go Test
x]
  where
    go :: Test -> SpecTree ()
    go :: Test -> SpecTree ()
go Test
t_ = case Test
t_ of
      TestLabel String
s (TestCase Assertion
e) -> forall a.
(HasCallStack, Example a) =>
String -> a -> SpecTree (Arg a)
specItem String
s Assertion
e
      TestLabel String
s (TestList [Test]
xs) -> forall a. HasCallStack => String -> [SpecTree a] -> SpecTree a
specGroup String
s (forall a b. (a -> b) -> [a] -> [b]
map Test -> SpecTree ()
go [Test]
xs)
      TestLabel String
s Test
x -> forall a. HasCallStack => String -> [SpecTree a] -> SpecTree a
specGroup String
s [Test -> SpecTree ()
go Test
x]
      TestList [Test]
xs -> forall a. HasCallStack => String -> [SpecTree a] -> SpecTree a
specGroup String
"<unlabeled>" (forall a b. (a -> b) -> [a] -> [b]
map Test -> SpecTree ()
go [Test]
xs)
      TestCase Assertion
e -> forall a.
(HasCallStack, Example a) =>
String -> a -> SpecTree (Arg a)
specItem String
"<unlabeled>" Assertion
e