diff options
| author | Simon Hengel <sol@typeful.net> | 2012-09-24 10:07:44 +0200 | 
|---|---|---|
| committer | Simon Hengel <sol@typeful.net> | 2012-10-01 11:30:51 +0200 | 
| commit | 25badd84cf6e09f4e556c7511a78144d38578d9f (patch) | |
| tree | ed4d4d778e249b8991c62e37e837263a3484fd54 /tests/nanospec | |
| parent | c0d71b685dfdcbafa8ca0b3924aef6629142e6dc (diff) | |
Add test-suite section for parsetests to cabal file
+ get rid of HUnit dependency
Diffstat (limited to 'tests/nanospec')
| -rw-r--r-- | tests/nanospec/README | 6 | ||||
| -rw-r--r-- | tests/nanospec/Test/Hspec.hs | 126 | 
2 files changed, 132 insertions, 0 deletions
| diff --git a/tests/nanospec/README b/tests/nanospec/README new file mode 100644 index 00000000..ffce7c74 --- /dev/null +++ b/tests/nanospec/README @@ -0,0 +1,6 @@ +A lightweight implementation of a subset of Hspec's API with minimal +dependencies. + +http://hackage.haskell.org/package/nanospec + +This is a copy of version 0.1.0. diff --git a/tests/nanospec/Test/Hspec.hs b/tests/nanospec/Test/Hspec.hs new file mode 100644 index 00000000..904ce2e0 --- /dev/null +++ b/tests/nanospec/Test/Hspec.hs @@ -0,0 +1,126 @@ +{-# LANGUAGE DeriveDataTypeable, CPP #-} +-- | A lightweight implementation of a subset of Hspec's API. +module Test.Hspec ( +-- * Types +  SpecM +, Spec + +-- * Defining a spec +, describe +, context +, it + +-- ** Setting expectations +, Expectation +, expect +, shouldBe +, shouldReturn + +-- * Running a spec +, hspec +) where + +import           Control.Applicative +import           Control.Monad +import           Data.Monoid +import           Data.List (intercalate) +import           Data.Typeable +import qualified Control.Exception as E +import           System.Exit + +-- a writer monad +data SpecM a = SpecM a [SpecTree] + +add :: SpecTree -> SpecM () +add s = SpecM () [s] + +instance Monad SpecM where +  return a             = SpecM a [] +  SpecM a xs >>= f = case f a of +    SpecM b ys -> SpecM b (xs ++ ys) + +data SpecTree = SpecGroup String Spec +              | SpecExample String (IO Result) + +data Result = Success | Failure String +  deriving (Eq, Show) + +type Spec = SpecM () + +describe :: String -> Spec -> Spec +describe label = add . SpecGroup label + +context :: String -> Spec -> Spec +context = describe + +it :: String -> Expectation -> Spec +it label = add . SpecExample label . evaluateExpectation + +-- | Summary of a test run. +data Summary = Summary Int Int + +instance Monoid Summary where +  mempty = Summary 0 0 +  (Summary x1 x2) `mappend` (Summary y1 y2) = Summary (x1 + y1) (x2 + y2) + +runSpec :: Spec -> IO Summary +runSpec = runForrest [] +  where +    runForrest :: [String] -> Spec -> IO Summary +    runForrest labels (SpecM () xs) = mconcat <$> mapM (runTree labels) xs + +    runTree :: [String] -> SpecTree -> IO Summary +    runTree labels spec = case spec of +      SpecExample label x -> do +        putStr $ "/" ++ (intercalate "/" . reverse) (label:labels) ++ "/ " +        r <- x +        case r of +          Success   -> do +            putStrLn "OK" +            return (Summary 1 0) +          Failure err -> do +            putStrLn "FAILED" +            putStrLn err +            return (Summary 1 1) +      SpecGroup label xs  -> do +        runForrest (label:labels) xs + +hspec :: Spec -> IO () +hspec spec = do +  Summary total failures <- runSpec spec +  putStrLn (show total ++ " example(s), " ++ show failures ++ " failure(s)") +  when (failures /= 0) exitFailure + +type Expectation = IO () + +infix 1 `shouldBe`, `shouldReturn` + +shouldBe :: (Show a, Eq a) => a -> a -> Expectation +actual `shouldBe` expected = +  expect ("expected: " ++ show expected ++ "\n but got: " ++ show actual) (actual == expected) + +shouldReturn :: (Show a, Eq a) => IO a -> a -> Expectation +action `shouldReturn` expected = action >>= (`shouldBe` expected) + +expect :: String -> Bool -> Expectation +expect label f +  | f         = return () +  | otherwise = E.throwIO (ExpectationFailure label) + +data ExpectationFailure = ExpectationFailure String +  deriving (Show, Eq, Typeable) + +instance E.Exception ExpectationFailure + +evaluateExpectation :: Expectation -> IO Result +evaluateExpectation action = (action >> return Success) +  `E.catches` [ +  -- Re-throw AsyncException, otherwise execution will not terminate on SIGINT +  -- (ctrl-c).  All AsyncExceptions are re-thrown (not just UserInterrupt) +  -- because all of them indicate severe conditions and should not occur during +  -- normal operation. +    E.Handler $ \e -> E.throw (e :: E.AsyncException) + +  , E.Handler $ \(ExpectationFailure err) -> return (Failure err) +  , E.Handler $ \e -> (return . Failure) ("*** Exception: " ++ show (e :: E.SomeException)) +  ] | 
