File: ExampleSpec.hs

package info (click to toggle)
haskell-hspec-core 2.11.9-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 656 kB
  • sloc: haskell: 8,945; makefile: 5
file content (257 lines) | stat: -rw-r--r-- 10,427 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}

module Test.Hspec.Core.ExampleSpec (spec) where

import           Prelude ()
import           Helper

import           Mock
import           Test.HUnit (assertFailure, assertEqual)

import           Test.Hspec.Core.Example (Result(..), ResultStatus(..), FailureReason(..))
import qualified Test.Hspec.Expectations as H
import qualified Test.Hspec.Core.Example as H
import qualified Test.Hspec.Core.Spec as H
import qualified Test.Hspec.Core.Runner as H

safeEvaluateExample :: (H.Example e,  H.Arg e ~ ()) => e -> IO Result
safeEvaluateExample e = H.safeEvaluateExample e defaultParams ($ ()) noOpProgressCallback

evaluateExample :: (H.Example e,  H.Arg e ~ ()) => e -> IO Result
evaluateExample e = H.evaluateExample e defaultParams ($ ()) noOpProgressCallback

evaluateExampleWith :: (H.Example e, H.Arg e ~ ()) => (IO () -> IO ()) -> e -> IO Result
evaluateExampleWith action e = H.evaluateExample e defaultParams (action . ($ ())) noOpProgressCallback

evaluateExampleWithArgument :: H.Example e => (ActionWith (H.Arg e) -> IO ()) -> e -> IO Result
evaluateExampleWithArgument action e = H.evaluateExample e defaultParams action noOpProgressCallback

bottom :: a
bottom = throw DivideByZero

spec :: Spec
spec = do
  describe "safeEvaluate" $ do
    let
      status :: ResultStatus
      status = Failure Nothing (Error Nothing $ toException DivideByZero)

      err :: Result
      err = Result "" status

    it "forces Result" $ do
      H.safeEvaluate (return $ Result "" bottom) `shouldReturn` err

    it "handles ResultStatus exceptions" $ do
      H.safeEvaluate (throwIO status) `shouldReturn` err

    it "forces ResultStatus exceptions" $ do
      H.safeEvaluate (throwIO $ Failure Nothing bottom) `shouldReturn` err

    it "handles other exceptions" $ do
      H.safeEvaluate (throwIO DivideByZero) `shouldReturn` err

    it "forces other exceptions" $ do
      H.safeEvaluate (throwIO $ ErrorCall bottom) `shouldReturn` err

  describe "safeEvaluateResultStatus" $ do
    let
      err :: ResultStatus
      err = Failure Nothing (Error Nothing $ toException DivideByZero)

    it "forces ResultStatus" $ do
      H.safeEvaluateResultStatus (return $ Failure Nothing bottom) `shouldReturn` err

    it "handles ResultStatus exceptions" $ do
      H.safeEvaluateResultStatus (throwIO err) `shouldReturn` err

    it "forces ResultStatus exceptions" $ do
      H.safeEvaluateResultStatus (throwIO $ Failure Nothing bottom) `shouldReturn` err

    it "handles other exceptions" $ do
      H.safeEvaluateResultStatus (throwIO DivideByZero) `shouldReturn` err

    it "forces other exceptions" $ do
      H.safeEvaluateResultStatus (throwIO $ ErrorCall bottom) `shouldReturn` err

  describe "safeEvaluateExample" $ do
    context "for Expectation" $ do
      it "returns Failure if an expectation does not hold" $ do
        Result "" (Failure _ msg) <- safeEvaluateExample (23 `H.shouldBe` (42 :: Int))
        msg `shouldBe` ExpectedButGot Nothing "42" "23"

      context "when used with `pending`" $ do
        it "returns Pending" $ do
          result <- safeEvaluateExample (H.pending)
          let location = mkLocation __FILE__ (pred __LINE__) 42
          result `shouldBe` Result "" (Pending location Nothing)

      context "when used with `pendingWith`" $ do
        it "includes the optional reason" $ do
          result <- safeEvaluateExample (H.pendingWith "foo")
          let location = mkLocation __FILE__ (pred __LINE__) 42
          result `shouldBe` Result "" (Pending location $ Just "foo")

  describe "evaluateExample" $ do
    context "for Result" $ do
      it "propagates exceptions" $ do
        evaluateExample (error "foobar" :: Result) `shouldThrow` errorCall "foobar"

      it "runs around-action" $ do
        ref <- newIORef (0 :: Int)
        let action :: IO () -> IO ()
            action e = do
              e
              modifyIORef ref succ

            result = Result "" (Failure Nothing NoReason)
        evaluateExampleWith action result `shouldReturn` result
        readIORef ref `shouldReturn` 1

      it "accepts arguments" $ do
        ref <- newIORef (0 :: Int)
        let action :: (Integer -> IO ()) -> IO ()
            action e = do
              e 42
              modifyIORef ref succ
        evaluateExampleWithArgument action (Result "" . Failure Nothing . Reason . show) `shouldReturn` Result "" (Failure Nothing $ Reason "42")
        readIORef ref `shouldReturn` 1

    context "for Bool" $ do
      it "returns Success on True" $ do
        evaluateExample True `shouldReturn` Result "" Success

      it "returns Failure on False" $ do
        evaluateExample False `shouldReturn` Result "" (Failure Nothing NoReason)

      it "propagates exceptions" $ do
        evaluateExample (error "foobar" :: Bool) `shouldThrow` errorCall "foobar"

      it "runs around-action" $ do
        ref <- newIORef (0 :: Int)
        let action :: IO () -> IO ()
            action e = do
              e
              modifyIORef ref succ
        evaluateExampleWith action False `shouldReturn` Result "" (Failure Nothing NoReason)
        readIORef ref `shouldReturn` 1

      it "accepts arguments" $ do
        ref <- newIORef (0 :: Int)
        let action :: (Integer -> IO ()) -> IO ()
            action e = do
              e 42
              modifyIORef ref succ
        evaluateExampleWithArgument action (== (23 :: Integer)) `shouldReturn` Result "" (Failure Nothing NoReason)
        readIORef ref `shouldReturn` 1

    context "for Expectation" $ do
      it "returns Success if all expectations hold" $ do
        evaluateExample (23 `shouldBe` (23 :: Int)) `shouldReturn` Result "" Success

      it "propagates exceptions" $ do
        evaluateExample (error "foobar" :: Expectation) `shouldThrow` errorCall "foobar"

      it "runs around-action" $ do
        ref <- newIORef (0 :: Int)
        let action :: IO () -> IO ()
            action e = do
              n <- readIORef ref
              e
              readIORef ref `shouldReturn` succ n
              modifyIORef ref succ
        evaluateExampleWith action (modifyIORef ref succ) `shouldReturn` Result "" Success
        readIORef ref `shouldReturn` 2

    context "for Property" $ do
      it "returns Success if property holds" $ do
        evaluateExample (property $ \n -> n == (n :: Int)) `shouldReturn` Result "+++ OK, passed 1000 tests." Success

      it "shows the collected labels" $ do
        Result info Success <- evaluateExample $ property $ \ () -> label "unit" True
        info `shouldBe` "+++ OK, passed 1000 tests (100.0% unit)."

      it "returns Failure if property does not hold" $ do
        Result "" (Failure _ _) <- evaluateExample $ property $ \n -> n /= (n :: Int)
        pass

      it "shows what falsified it" $ do
        Result "" (Failure _ r) <- evaluateExample $ property $ \ (x :: Int) (y :: Int) -> (x == 0 && y == 1) ==> False
        r `shouldBe` (Reason . intercalate "\n")  [
            "Falsified (after 1 test):"
          , "  0"
          , "  1"
          ]

      it "runs around-action for each single check of the property" $ do
        ref <- newIORef (0 :: Int)
        let action :: IO () -> IO ()
            action e = do
              n <- readIORef ref
              e
              readIORef ref `shouldReturn` succ n
              modifyIORef ref succ
        Result _ Success <- evaluateExampleWith action (property $ \(_ :: Int) -> modifyIORef ref succ)
        readIORef ref `shouldReturn` 2000

      it "pretty-prints exceptions" $ do
        Result "" (Failure _ r) <- evaluateExample $ property (\ (x :: Int) -> (x == 0) ==> (throw (ErrorCall "foobar") :: Bool))
        r `shouldBe` (Reason . intercalate "\n") [
            "uncaught exception: ErrorCall"
          , "foobar"
          , "(after 1 test)"
          , "  0"
          ]

      context "when used with Expectation" $ do
        let prop p = property $ \ (x :: Int) (y :: Int) -> (x == 0 && y == 1) ==> p
        context "when used with shouldBe" $ do
          it "shows what falsified it" $ do
            Result "" (Failure _ err) <- evaluateExample $ prop $ 23 `H.shouldBe` (42 :: Int)
            err `shouldBe` ExpectedButGot (Just "Falsifiable (after 1 test):\n  0\n  1") "42" "23"

        context "when used with assertEqual" $ do
          it "includes prefix" $ do
            Result "" (Failure _ err) <- evaluateExample $ prop $ assertEqual "foobar" (42 :: Int) 23
            err `shouldBe` ExpectedButGot (Just "Falsifiable (after 1 test):\n  0\n  1\nfoobar") "42" "23"

        context "when used with assertFailure" $ do
          it "includes reason" $ do
            Result "" (Failure _ err) <- evaluateExample $ prop (assertFailure "foobar" :: IO ())
            err `shouldBe` Reason "Falsifiable (after 1 test):\n  0\n  1\nfoobar"

        context "when used with verbose" $ do
          it "includes verbose output" $ do
            Result info (Failure _ err) <- evaluateExample $ verbose $ (`H.shouldBe` (23 :: Int))
            info `shouldBe` "Failed:\n0"
            err `shouldBe` ExpectedButGot (Just "Falsifiable (after 1 test):\n  0") "23" "0"

      context "when used with `pending`" $ do
        it "returns Pending" $ do
          let location = mkLocation __FILE__ (succ __LINE__) 37
          evaluateExample (property H.pending) `shouldReturn` Result "" (Pending location Nothing)

      context "when used with `pendingWith`" $ do
        it "includes the optional reason" $ do
          let location = mkLocation __FILE__ (succ __LINE__) 39
          evaluateExample (property $ H.pendingWith "foo") `shouldReturn` Result "" (Pending location $ Just "foo")

  describe "Expectation" $ do
    context "as a QuickCheck property" $ do
      it "can be quantified" $ do
        e <- newMock
        hspecSilent $ do
          H.it "some behavior" $ property $ \xs -> do
            mockAction e
            (reverse . reverse) xs `shouldBe` (xs :: [Int])
        mockCounter e `shouldReturn` 100

      it "can be used with expectations/HUnit assertions" $ do
        hspecResultSilent $ do
          H.describe "readIO" $ do
            H.it "is inverse to show" $ property $ \x -> do
              (readIO . show) x `shouldReturn` (x :: Int)
        `shouldReturn` H.Summary 1 0