diff --git a/Specs.hs b/Specs.hs index 0e6bd25bb..709f5a72a 100644 --- a/Specs.hs +++ b/Specs.hs @@ -2,7 +2,7 @@ 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 @@ -10,14 +10,10 @@ 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 diff --git a/Test/Hspec.hs b/Test/Hspec.hs index d0d5b2303..a4ca9d5f1 100644 --- a/Test/Hspec.hs +++ b/Test/Hspec.hs @@ -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 diff --git a/Test/Hspec/Core.hs b/Test/Hspec/Core.hs index b4c1cb36c..33ad10c7c 100644 --- a/Test/Hspec/Core.hs +++ b/Test/Hspec/Core.hs @@ -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 diff --git a/Test/Hspec/Monadic.hs b/Test/Hspec/Monadic.hs index 29462f185..31b0255b3 100644 --- a/Test/Hspec/Monadic.hs +++ b/Test/Hspec/Monadic.hs @@ -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 @@ -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. -- @@ -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 @@ -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) diff --git a/Test/Hspec/Runner.hs b/Test/Hspec/Runner.hs index 916d63b6d..3b7abfbef 100644 --- a/Test/Hspec/Runner.hs +++ b/Test/Hspec/Runner.hs @@ -3,7 +3,7 @@ -- 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 @@ -11,6 +11,7 @@ import Test.Hspec.Formatters import System.IO import System.CPUTime (getCPUTime) import Control.Monad (when) +import System.Exit type Specs = [IO Spec] @@ -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] @@ -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 +