Skip to content

Commit

Permalink
revive hspecX
Browse files Browse the repository at this point in the history
  • Loading branch information
gregwebs committed May 21, 2011
1 parent 070205f commit 7cf254e
Show file tree
Hide file tree
Showing 5 changed files with 34 additions and 12 deletions.
8 changes: 2 additions & 6 deletions Specs.hs
Expand Up @@ -2,22 +2,18 @@
module Specs where

import Test.Hspec
import Test.Hspec.Runner (hHspecWithFormat)
import Test.Hspec.Runner (hHspecWithFormat, toExitCode)
import Test.Hspec.Core (Spec(..),Result(..),quantify,failedCount)
import Test.Hspec.Formatters (specdoc)
import Test.Hspec.QuickCheck
import Test.Hspec.HUnit ()
import System.IO
import System.IO.Silently
import System.Environment
import System.Exit
import System.Exit (exitWith)
import Data.List (isPrefixOf)
import qualified Test.HUnit as HUnit

toExitCode :: Bool -> ExitCode
toExitCode True = ExitSuccess
toExitCode False = ExitFailure 1

main :: IO ()
main = do
ar <- getArgs
Expand Down
2 changes: 1 addition & 1 deletion Test/Hspec.hs
Expand Up @@ -75,7 +75,7 @@ module Test.Hspec (
-- types
Spec(), Result(),Specs,
-- the main api
describe, it, hspec, pending, descriptions,
describe, it, hspec, hspecB, hspecX, pending, descriptions,
-- alternate "runner" functions
hHspec
) where
Expand Down
8 changes: 7 additions & 1 deletion Test/Hspec/Core.hs
Expand Up @@ -94,10 +94,16 @@ pending :: String -- ^ An explanation for why this behavior is pending.
pending = Pending



failedCount :: [Spec] -> Int
failedCount ss = length $ filter (isFailure.result) ss

failure :: [Spec] -> Bool
failure = any (isFailure.result)

success :: [Spec] -> Bool
success = not . failure


isFailure :: Result -> Bool
isFailure (Fail _) = True
isFailure _ = False
Expand Down
14 changes: 11 additions & 3 deletions Test/Hspec/Monadic.hs
Expand Up @@ -11,7 +11,7 @@
-- > import Test.QuickCheck hiding (property)
-- > import Test.HUnit
-- >
-- > main = hspec mySpecs
-- > main = hspecX $ do
--
-- Since the specs are often used to tell you what to implement, it's best to start with
-- undefined functions. Once we have some specs, then you can implement each behavior
Expand All @@ -25,7 +25,7 @@
--
-- The "describe" function takes a list of behaviors and examples bound together with the "it" function
--
-- > mySpecs = describe "unformatPhoneNumber" $ do
-- > describe "unformatPhoneNumber" $ do
--
-- A boolean expression can act as a behavior's example.
--
Expand Down Expand Up @@ -67,7 +67,7 @@ module Test.Hspec.Monadic (
-- types
Spec(), Result(),Specs,
-- the main api
describe, it, hspec, pending, descriptions,
describe, it, hspec, hspecB, hspecX, pending, descriptions,
-- alternate "runner" functions
hHspec,
-- this is just for internal use
Expand All @@ -90,6 +90,14 @@ type Specs = Writer [IO [IO Spec]] ()
hspec :: Specs -> IO [Spec]
hspec = Runner.hspec . runSpecM

-- | Use in place of @hspec@ to also exit the program with an @ExitCode@
hspecX :: Specs -> IO a
hspecX = Runner.hspecX . runSpecM

-- | Use in place of hspec to also give a @Bool@ success indication
hspecB :: Specs -> IO Bool
hspecB = Runner.hspecB . runSpecM

-- | Create a document of the given specs and write it to the given handle.
--
-- > writeReport filename specs = withFile filename WriteMode (\ h -> hHspec h specs)
Expand Down
14 changes: 13 additions & 1 deletion Test/Hspec/Runner.hs
Expand Up @@ -3,14 +3,15 @@
-- report to a given handle.
--
module Test.Hspec.Runner (
Specs, hspec, hHspec, hHspecWithFormat, describe, it
Specs, hspec, hspecX, hspecB, hHspec, hHspecWithFormat, describe, it, toExitCode
) where

import Test.Hspec.Core
import Test.Hspec.Formatters
import System.IO
import System.CPUTime (getCPUTime)
import Control.Monad (when)
import System.Exit

type Specs = [IO Spec]

Expand All @@ -37,6 +38,13 @@ errorDetails spec i = case result spec of
(Fail s ) -> concat [ show (i + 1), ") ", name spec, " ", requirement spec, " FAILED", if null s then "" else "\n" ++ s ]
_ -> ""

-- | Use in place of @hspec@ to also exit the program with an @ExitCode@
hspecX :: IO Specs -> IO a
hspecX ss = hspecB ss >>= exitWith . toExitCode

-- | Use in place of hspec to also give a @Bool@ success indication
hspecB :: IO Specs -> IO Bool
hspecB ss = hspec ss >>= return . success

-- | Create a document of the given specs and write it to stdout.
hspec :: IO Specs -> IO [Spec]
Expand All @@ -61,3 +69,7 @@ hHspecWithFormat formatter h ss = do
(footerFormatter formatter) h specList runTime
return specList

toExitCode :: Bool -> ExitCode
toExitCode True = ExitSuccess
toExitCode False = ExitFailure 1

0 comments on commit 7cf254e

Please sign in to comment.