Hello community,

here is the log from the commit of package ghc-hspec-core for openSUSE:Factory 
checked in at 2020-09-07 21:21:57
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-hspec-core (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-hspec-core.new.3399 (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-hspec-core"

Mon Sep  7 21:21:57 2020 rev:14 rq:831210 version:2.7.4

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-hspec-core/ghc-hspec-core.changes    
2019-12-27 13:54:09.428681168 +0100
+++ /work/SRC/openSUSE:Factory/.ghc-hspec-core.new.3399/ghc-hspec-core.changes  
2020-09-07 21:22:04.573014917 +0200
@@ -1,0 +2,6 @@
+Tue Sep  1 14:41:20 UTC 2020 - [email protected]
+
+- Update hspec-core to version 2.7.4.
+  Upstream does not provide a change log file.
+
+-------------------------------------------------------------------

Old:
----
  hspec-core-2.7.1.tar.gz
  hspec-core.cabal

New:
----
  hspec-core-2.7.4.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-hspec-core.spec ++++++
--- /var/tmp/diff_new_pack.ABE7b5/_old  2020-09-07 21:22:08.941016921 +0200
+++ /var/tmp/diff_new_pack.ABE7b5/_new  2020-09-07 21:22:08.945016923 +0200
@@ -1,7 +1,7 @@
 #
 # spec file for package ghc-hspec-core
 #
-# Copyright (c) 2019 SUSE LINUX GmbH, Nuernberg, Germany.
+# Copyright (c) 2020 SUSE LLC
 #
 # All modifications and additions to the file contributed by third parties
 # remain the property of their copyright owners, unless otherwise agreed
@@ -19,13 +19,12 @@
 %global pkg_name hspec-core
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        2.7.1
+Version:        2.7.4
 Release:        0
 Summary:        A Testing Framework for Haskell
 License:        MIT
 URL:            https://hackage.haskell.org/package/%{pkg_name}
 Source0:        
https://hackage.haskell.org/package/%{pkg_name}-%{version}/%{pkg_name}-%{version}.tar.gz
-Source1:        
https://hackage.haskell.org/package/%{pkg_name}-%{version}/revision/1.cabal#/%{pkg_name}.cabal
 BuildRequires:  ghc-Cabal-devel
 BuildRequires:  ghc-HUnit-devel
 BuildRequires:  ghc-QuickCheck-devel
@@ -66,8 +65,7 @@
 This package provides the Haskell %{pkg_name} library development files.
 
 %prep
-%setup -q -n %{pkg_name}-%{version}
-cp -p %{SOURCE1} %{pkg_name}.cabal
+%autosetup -n %{pkg_name}-%{version}
 
 %build
 %ghc_lib_build

++++++ hspec-core-2.7.1.tar.gz -> hspec-core-2.7.4.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/hspec-core.cabal 
new/hspec-core-2.7.4/hspec-core.cabal
--- old/hspec-core-2.7.1/hspec-core.cabal       2019-03-29 13:56:43.000000000 
+0100
+++ new/hspec-core-2.7.4/hspec-core.cabal       2020-09-01 14:11:21.000000000 
+0200
@@ -1,13 +1,11 @@
 cabal-version: 1.12
 
--- This file has been generated from package.yaml by hpack version 0.31.0.
+-- This file has been generated from package.yaml by hpack version 0.34.2.
 --
 -- see: https://github.com/sol/hpack
---
--- hash: 82bf612e65db816a15de01c4c432597ef4492ceeb81f46063dcdd57b74ec523a
 
 name:             hspec-core
-version:          2.7.1
+version:          2.7.4
 license:          MIT
 license-file:     LICENSE
 copyright:        (c) 2011-2019 Simon Hengel,
@@ -39,7 +37,7 @@
     , array
     , base >=4.5.0.0 && <5
     , call-stack
-    , clock
+    , clock >=0.7.1
     , deepseq
     , directory
     , filepath
@@ -73,6 +71,7 @@
       Test.Hspec.Core.Formatters.Monad
       Test.Hspec.Core.QuickCheckUtil
       Test.Hspec.Core.Runner.Eval
+      Test.Hspec.Core.Shuffle
       Test.Hspec.Core.Spec.Monad
       Test.Hspec.Core.Timer
       Test.Hspec.Core.Tree
@@ -92,12 +91,12 @@
   cpp-options: -DTEST
   build-depends:
       HUnit ==1.6.*
-    , QuickCheck >=2.13.1
+    , QuickCheck >=2.14
     , ansi-terminal >=0.5
     , array
     , base >=4.5.0.0 && <5
     , call-stack
-    , clock
+    , clock >=0.7.1
     , deepseq
     , directory
     , filepath
@@ -134,6 +133,7 @@
       Test.Hspec.Core.QuickCheckUtil
       Test.Hspec.Core.Runner
       Test.Hspec.Core.Runner.Eval
+      Test.Hspec.Core.Shuffle
       Test.Hspec.Core.Spec
       Test.Hspec.Core.Spec.Monad
       Test.Hspec.Core.Timer
@@ -158,6 +158,7 @@
       Test.Hspec.Core.QuickCheckUtilSpec
       Test.Hspec.Core.Runner.EvalSpec
       Test.Hspec.Core.RunnerSpec
+      Test.Hspec.Core.ShuffleSpec
       Test.Hspec.Core.SpecSpec
       Test.Hspec.Core.TimerSpec
       Test.Hspec.Core.UtilSpec
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/src/Test/Hspec/Core/Clock.hs 
new/hspec-core-2.7.4/src/Test/Hspec/Core/Clock.hs
--- old/hspec-core-2.7.1/src/Test/Hspec/Core/Clock.hs   2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/src/Test/Hspec/Core/Clock.hs   2020-09-01 
14:11:21.000000000 +0200
@@ -5,11 +5,13 @@
 , getMonotonicTime
 , measure
 , sleep
+, timeout
 ) where
 
 import           Text.Printf
 import           System.Clock
 import           Control.Concurrent
+import qualified System.Timeout as System
 
 newtype Seconds = Seconds Double
   deriving (Eq, Show, Num, Fractional, PrintfArg)
@@ -31,3 +33,6 @@
 
 sleep :: Seconds -> IO ()
 sleep = threadDelay . toMicroseconds
+
+timeout :: Seconds -> IO a -> IO (Maybe a)
+timeout = System.timeout . toMicroseconds
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/hspec-core-2.7.1/src/Test/Hspec/Core/Config/Options.hs 
new/hspec-core-2.7.4/src/Test/Hspec/Core/Config/Options.hs
--- old/hspec-core-2.7.1/src/Test/Hspec/Core/Config/Options.hs  2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/src/Test/Hspec/Core/Config/Options.hs  2020-09-01 
14:11:21.000000000 +0200
@@ -37,6 +37,7 @@
 , configFailOnFocused :: Bool
 , configPrintCpuTime :: Bool
 , configFastFail :: Bool
+, configRandomize :: Bool
 , configFailureReport :: Maybe FilePath
 , configRerun :: Bool
 , configRerunAllOnSuccess :: Bool
@@ -67,6 +68,7 @@
 , configFailOnFocused = False
 , configPrintCpuTime = False
 , configFastFail = False
+, configRandomize = False
 , configFailureReport = Nothing
 , configRerun = False
 , configRerunAllOnSuccess = False
@@ -199,10 +201,13 @@
   , mkFlag "focused-only" setFocusedOnly "do not run anything, unless there 
are focused spec items"
   , mkFlag "fail-on-focused" setFailOnFocused "fail on focused spec items"
   , mkFlag "fail-fast" setFastFail "abort on first failure"
+  , mkFlag "randomize" setRandomize "randomize execution order"
   ] ++ [
     Option "r" ["rerun"] (NoArg  setRerun) "rerun all examples that failed in 
the previous test run (only works in combination with --failure-report or in 
GHCi)"
   , mkOption [] "failure-report" (Arg "FILE" return setFailureReport) 
"read/write a failure report for use with --rerun"
   , Option [] ["rerun-all-on-success"] (NoArg setRerunAllOnSuccess) "run the 
whole test suite after a previously failing rerun succeeds for the first time 
(only works in combination with --rerun)"
+
+
   , mkOption "j" "jobs" (Arg "N" readMaxJobs setMaxJobs) "run at most N 
parallelizable tests simultaneously (default: number of available processors)"
   ]
   where
@@ -230,6 +235,9 @@
     setFastFail :: Bool -> Config -> Config
     setFastFail value config = config {configFastFail = value}
 
+    setRandomize :: Bool -> Config -> Config
+    setRandomize value config = config {configRandomize = value}
+
     setRerun        = set $ \config -> config {configRerun = True}
     setRerunAllOnSuccess = set $ \config -> config {configRerunAllOnSuccess = 
True}
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/src/Test/Hspec/Core/Formatters.hs 
new/hspec-core-2.7.4/src/Test/Hspec/Core/Formatters.hs
--- old/hspec-core-2.7.1/src/Test/Hspec/Core/Formatters.hs      2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/src/Test/Hspec/Core/Formatters.hs      2020-09-01 
14:11:21.000000000 +0200
@@ -61,8 +61,11 @@
 
 import           Data.Maybe
 import           Test.Hspec.Core.Util
+import           Test.Hspec.Core.Clock
 import           Test.Hspec.Core.Spec (Location(..))
 import           Text.Printf
+import           Control.Monad.IO.Class
+import           Control.Exception
 
 -- We use an explicit import list for "Test.Hspec.Formatters.Internal", to make
 -- sure, that we only use the public API to implement formatters.
@@ -100,8 +103,6 @@
   , missingChunk
   )
 
-import           Test.Hspec.Core.Clock (Seconds(..))
-
 import           Test.Hspec.Core.Formatters.Diff
 
 silent :: Formatter
@@ -212,28 +213,38 @@
           mapM_ indent preface
 
           b <- useDiff
-          let
-            chunks
-              | b = diff expected actual
-              | otherwise = [First expected, Second actual]
-
-          withFailColor $ write (indentation ++ "expected: ")
-          forM_ chunks $ \chunk -> case chunk of
-            Both a _ -> indented write a
-            First a -> indented extraChunk a
-            Second _ -> return ()
-          writeLine ""
-
-          withFailColor $ write (indentation ++ " but got: ")
-          forM_ chunks $ \chunk -> case chunk of
-            Both a _ -> indented write a
-            First _ -> return ()
-            Second a -> indented missingChunk a
-          writeLine ""
+
+          let threshold = 2 :: Seconds
+
+          mchunks <- liftIO $ if b
+            then timeout threshold (evaluate $ diff expected actual)
+            else return Nothing
+
+          case mchunks of
+            Just chunks -> do
+              writeDiff chunks extraChunk missingChunk
+            Nothing -> do
+              writeDiff [First expected, Second actual] write write
           where
             indented output text = case break (== '\n') text of
               (xs, "") -> output xs
               (xs, _ : ys) -> output (xs ++ "\n") >> write (indentation ++ "   
       ") >> indented output ys
+
+            writeDiff chunks extra missing = do
+              withFailColor $ write (indentation ++ "expected: ")
+              forM_ chunks $ \ chunk -> case chunk of
+                Both a _ -> indented write a
+                First a -> indented extra a
+                Second _ -> return ()
+              writeLine ""
+
+              withFailColor $ write (indentation ++ " but got: ")
+              forM_ chunks $ \ chunk -> case chunk of
+                Both a _ -> indented write a
+                First _ -> return ()
+                Second a -> indented missing a
+              writeLine ""
+
         Error _ e -> withFailColor . indent $ (("uncaught exception: " ++) . 
formatException) e
 
       writeLine ""
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/src/Test/Hspec/Core/Runner.hs 
new/hspec-core-2.7.4/src/Test/Hspec/Core/Runner.hs
--- old/hspec-core-2.7.1/src/Test/Hspec/Core/Runner.hs  2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/src/Test/Hspec/Core/Runner.hs  2020-09-01 
14:11:21.000000000 +0200
@@ -39,6 +39,9 @@
 import           System.Environment (getArgs, withArgs)
 import           System.Exit
 import qualified Control.Exception as E
+import           System.Random
+import           Control.Monad.ST
+import           Data.STRef
 
 import           System.Console.ANSI (hHideCursor, hShowCursor)
 import qualified Test.QuickCheck as QC
@@ -50,6 +53,7 @@
 import           Test.Hspec.Core.Formatters.Internal
 import           Test.Hspec.Core.FailureReport
 import           Test.Hspec.Core.QuickCheckUtil
+import           Test.Hspec.Core.Shuffle
 
 import           Test.Hspec.Core.Runner.Eval
 
@@ -219,8 +223,11 @@
     let
       focusedSpec = focusSpec config (failFocusedItems config spec)
       params = Params (configQuickCheckArgs config) (configSmallCheckDepth 
config)
+      randomize
+        | configRandomize config = randomizeForest seed
+        | otherwise = id
 
-    filteredSpec <- filterSpecs config . mapMaybe (toEvalTree params) . 
applyDryRun config <$> runSpecM focusedSpec
+    filteredSpec <- randomize . filterSpecs config . mapMaybe (toEvalTree 
params) . applyDryRun config <$> runSpecM focusedSpec
 
     (total, failures) <- withHiddenCursor useColor h $ do
       let
@@ -306,3 +313,8 @@
 instance Semigroup Summary where
   (Summary x1 x2) <> (Summary y1 y2) = Summary (x1 + y1) (x2 + y2)
 #endif
+
+randomizeForest :: Integer -> [Tree c a] -> [Tree c a]
+randomizeForest seed t = runST $ do
+  ref <- newSTRef (mkStdGen $ fromIntegral seed)
+  shuffleForest ref t
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/src/Test/Hspec/Core/Shuffle.hs 
new/hspec-core-2.7.4/src/Test/Hspec/Core/Shuffle.hs
--- old/hspec-core-2.7.1/src/Test/Hspec/Core/Shuffle.hs 1970-01-01 
01:00:00.000000000 +0100
+++ new/hspec-core-2.7.4/src/Test/Hspec/Core/Shuffle.hs 2020-09-01 
14:11:21.000000000 +0200
@@ -0,0 +1,45 @@
+{-# LANGUAGE CPP #-}
+module Test.Hspec.Core.Shuffle (
+  shuffleForest
+#ifdef TEST
+, shuffle
+, mkArray
+#endif
+) where
+
+import           Prelude ()
+import           Test.Hspec.Core.Compat
+import           Test.Hspec.Core.Tree
+
+import           System.Random
+import           Control.Monad.ST
+import           Data.STRef
+import           Data.Array.ST
+
+shuffleForest :: STRef s StdGen -> [Tree c a] -> ST s [Tree c a]
+shuffleForest ref xs = (shuffle ref xs >>= mapM (shuffleTree ref))
+
+shuffleTree :: STRef s StdGen -> Tree c a -> ST s (Tree c a)
+shuffleTree ref t = case t of
+  Node d xs -> Node d <$> shuffleForest ref xs
+  NodeWithCleanup c xs -> NodeWithCleanup c <$> shuffleForest ref xs
+  Leaf {} -> return t
+
+shuffle :: STRef s StdGen -> [a] -> ST s [a]
+shuffle ref xs = do
+  arr <- mkArray xs
+  bounds@(_, n) <- getBounds arr
+  forM (range bounds) $ \ i -> do
+    j <- randomIndex (i, n)
+    vi <- readArray arr i
+    vj <- readArray arr j
+    writeArray arr j vi
+    return vj
+  where
+    randomIndex bounds = do
+      (a, gen) <- randomR bounds <$> readSTRef ref
+      writeSTRef ref gen
+      return a
+
+mkArray :: [a] -> ST s (STArray s Int a)
+mkArray xs = newListArray (1, length xs) xs
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/test/Helper.hs 
new/hspec-core-2.7.4/test/Helper.hs
--- old/hspec-core-2.7.1/test/Helper.hs 2019-03-29 13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/test/Helper.hs 2020-09-01 14:11:21.000000000 +0200
@@ -36,7 +36,6 @@
 import           System.Exit
 import qualified Control.Exception as E
 import           Control.Exception
-import qualified System.Timeout as System
 import           System.IO.Silently
 import           System.SetEnv
 import           System.Directory
@@ -95,9 +94,6 @@
 noOpProgressCallback :: H.ProgressCallback
 noOpProgressCallback _ = return ()
 
-timeout :: Seconds -> IO a -> IO (Maybe a)
-timeout = System.timeout . toMicroseconds
-
 shouldUseArgs :: HasCallStack => [String] -> (Args -> Bool) -> Expectation
 shouldUseArgs args p = do
   spy <- newIORef (H.paramsQuickCheckArgs defaultParams)
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/test/Test/Hspec/Core/ConfigSpec.hs 
new/hspec-core-2.7.4/test/Test/Hspec/Core/ConfigSpec.hs
--- old/hspec-core-2.7.1/test/Test/Hspec/Core/ConfigSpec.hs     2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/test/Test/Hspec/Core/ConfigSpec.hs     2020-09-01 
14:11:21.000000000 +0200
@@ -8,7 +8,7 @@
 
 spec :: Spec
 spec = do
-  describe "readConfigFiles" $ around_ (withEnvironment []) $ around_ 
inTempDirectory $ do
+  describe "readConfigFiles" $ around_ inTempDirectory $ around_ 
(withEnvironment [("HOME", "/foo")]) $ do
     it "reads .hspec" $ do
       dir <- getCurrentDirectory
       let name = dir </> ".hspec"
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/hspec-core-2.7.1/test/Test/Hspec/Core/Example/LocationSpec.hs 
new/hspec-core-2.7.4/test/Test/Hspec/Core/Example/LocationSpec.hs
--- old/hspec-core-2.7.1/test/Test/Hspec/Core/Example/LocationSpec.hs   
2019-03-29 13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/test/Test/Hspec/Core/Example/LocationSpec.hs   
2020-09-01 14:11:21.000000000 +0200
@@ -1,6 +1,7 @@
 {-# LANGUAGE CPP #-}
 {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
 {-# OPTIONS_GHC -fno-warn-missing-fields #-}
+{-# OPTIONS_GHC -fno-warn-overlapping-patterns #-}
 module Test.Hspec.Core.Example.LocationSpec (spec) where
 
 import           Helper
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/hspec-core-2.7.1/test/Test/Hspec/Core/FormattersSpec.hs 
new/hspec-core-2.7.4/test/Test/Hspec/Core/FormattersSpec.hs
--- old/hspec-core-2.7.1/test/Test/Hspec/Core/FormattersSpec.hs 2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/test/Test/Hspec/Core/FormattersSpec.hs 2020-09-01 
14:11:21.000000000 +0200
@@ -5,6 +5,7 @@
 import           Prelude ()
 import           Helper
 import           Data.String
+import           Control.Monad.IO.Class
 import           Control.Monad.Trans.Writer
 import qualified Control.Exception as E
 
@@ -53,13 +54,13 @@
   Plain x : xs -> color x : xs
   xs -> xs
 
-interpret :: FormatM a -> [ColorizedText]
+interpret :: FormatM a -> IO [ColorizedText]
 interpret = interpretWith environment
 
-interpretWith :: Environment (Writer [ColorizedText]) -> FormatM a -> 
[ColorizedText]
-interpretWith env = simplify . execWriter . H.interpretWith env
+interpretWith :: Environment (WriterT [ColorizedText] IO) -> FormatM a -> IO 
[ColorizedText]
+interpretWith env = fmap simplify . execWriterT . H.interpretWith env
 
-environment :: Environment (Writer [ColorizedText])
+environment :: Environment (WriterT [ColorizedText] IO)
 environment = Environment {
   environmentGetSuccessCount = return 0
 , environmentGetPendingCount = return 0
@@ -69,14 +70,22 @@
 , environmentGetRealTime = return 0
 , environmentWrite = tell . return . Plain
 , environmentWriteTransient = tell . return . Transient
-, environmentWithFailColor = \action -> let (a, r) = runWriter action in tell 
(colorize Failed r) >> return a
-, environmentWithSuccessColor = \action -> let (a, r) = runWriter action in 
tell (colorize Succeeded r) >> return a
-, environmentWithPendingColor = \action -> let (a, r) = runWriter action in 
tell (colorize Pending r) >> return a
-, environmentWithInfoColor = \action -> let (a, r) = runWriter action in tell 
(colorize Info r) >> return a
+, environmentWithFailColor = \ action -> do
+    (a, r) <- liftIO $ runWriterT action
+    tell (colorize Failed r) >> return a
+, environmentWithSuccessColor = \ action -> do
+    (a, r) <- liftIO $ runWriterT action
+    tell (colorize Succeeded r) >> return a
+, environmentWithPendingColor = \ action -> do
+    (a, r) <- liftIO $ runWriterT action
+    tell (colorize Pending r) >> return a
+, environmentWithInfoColor = \ action -> do
+    (a, r) <- liftIO $ runWriterT action
+    tell (colorize Info r) >> return a
 , environmentUseDiff = return True
 , environmentExtraChunk = tell . return . Extra
 , environmentMissingChunk = tell . return . Missing
-, environmentLiftIO = undefined
+, environmentLiftIO = liftIO
 }
 
 testSpec :: H.Spec
@@ -96,19 +105,19 @@
 
     describe "exampleSucceeded" $ do
       it "marks succeeding examples with ." $ do
-        interpret (H.exampleSucceeded formatter undefined undefined) 
`shouldBe` [
+        interpret (H.exampleSucceeded formatter undefined undefined) 
`shouldReturn` [
             Succeeded "."
           ]
 
     describe "exampleFailed" $ do
       it "marks failing examples with F" $ do
-        interpret (H.exampleFailed formatter undefined undefined undefined) 
`shouldBe` [
+        interpret (H.exampleFailed formatter undefined undefined undefined) 
`shouldReturn` [
             Failed "F"
           ]
 
     describe "examplePending" $ do
       it "marks pending examples with ." $ do
-        interpret (H.examplePending formatter undefined undefined undefined) 
`shouldBe` [
+        interpret (H.examplePending formatter undefined undefined undefined) 
`shouldReturn` [
             Pending "."
           ]
 
@@ -206,7 +215,7 @@
             environmentGetFailMessages = return [FailureRecord Nothing ([], 
"") (ExpectedButGot Nothing "first\nsecond\nthird" "first\ntwo\nthird")]
             }
         it "adds indentation" $ do
-          removeColors (interpretWith env action) `shouldBe` unlines [
+          (removeColors <$> interpretWith env action) `shouldReturn` unlines [
               ""
             , "Failures:"
             , ""
@@ -238,7 +247,7 @@
       context "without failures" $ do
         let env = environment {environmentGetSuccessCount = return 1}
         it "shows summary in green if there are no failures" $ do
-          interpretWith env action `shouldBe` [
+          interpretWith env action `shouldReturn` [
               "Finished in 0.0000 seconds\n"
             , Succeeded "1 example, 0 failures\n"
             ]
@@ -246,7 +255,7 @@
       context "with pending examples" $ do
         let env = environment {environmentGetPendingCount = return 1}
         it "shows summary in yellow if there are pending examples" $ do
-          interpretWith env action `shouldBe` [
+          interpretWith env action `shouldReturn` [
               "Finished in 0.0000 seconds\n"
             , Pending "1 example, 0 failures, 1 pending\n"
             ]
@@ -254,7 +263,7 @@
       context "with failures" $ do
         let env = environment {environmentGetFailMessages = return [undefined]}
         it "shows summary in red" $ do
-          interpretWith env action `shouldBe` [
+          interpretWith env action `shouldReturn` [
               "Finished in 0.0000 seconds\n"
             , Failed "1 example, 1 failure\n"
             ]
@@ -262,7 +271,7 @@
       context "with both failures and pending examples" $ do
         let env = environment {environmentGetFailMessages = return 
[undefined], environmentGetPendingCount = return 1}
         it "shows summary in red" $ do
-          interpretWith env action `shouldBe` [
+          interpretWith env action `shouldReturn` [
               "Finished in 0.0000 seconds\n"
             , Failed "2 examples, 1 failure, 1 pending\n"
             ]
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/hspec-core-2.7.1/test/Test/Hspec/Core/QuickCheckUtilSpec.hs 
new/hspec-core-2.7.4/test/Test/Hspec/Core/QuickCheckUtilSpec.hs
--- old/hspec-core-2.7.1/test/Test/Hspec/Core/QuickCheckUtilSpec.hs     
2019-03-29 13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/test/Test/Hspec/Core/QuickCheckUtilSpec.hs     
2020-09-01 14:11:21.000000000 +0200
@@ -91,7 +91,7 @@
             , "0"
             , ""
             , "Passed:"
-            , "28"
+            , "23"
             ]
         parseQuickCheckResult <$> quickCheckWithResult args {maxSuccess = 2} 
(verbose p) `shouldReturn`
           QuickCheckResult 2 info (QuickCheckOtherFailure "Passed 2 tests 
(expected failure).")
@@ -100,11 +100,11 @@
       context "without checkCoverage" $ do
         let
           p :: Int -> Property
-          p n = cover 10 (n == 23) "is 23" True
+          p n = cover 10 (n == 5) "is 5" True
 
         it "parses result" $ do
           parseQuickCheckResult <$> qc p `shouldReturn`
-            QuickCheckResult 100 "+++ OK, passed 100 tests.\n\nOnly 0% is 23, 
but expected 10%" QuickCheckSuccess
+            QuickCheckResult 100 "+++ OK, passed 100 tests (1% is 5).\n\nOnly 
1% is 5, but expected 10%" QuickCheckSuccess
 
         it "includes verbose output" $ do
           let
@@ -113,11 +113,11 @@
               , "0"
               , ""
               , "Passed:"
-              , "28"
+              , "23"
               , ""
               , "+++ OK, passed 2 tests."
               , ""
-              , "Only 0% is 23, but expected 10%"
+              , "Only 0% is 5, but expected 10%"
               ]
           parseQuickCheckResult <$> quickCheckWithResult args {maxSuccess = 2} 
(verbose p) `shouldReturn`
             QuickCheckResult 2 info QuickCheckSuccess
@@ -133,20 +133,20 @@
             , quickCheckFailureException = Nothing
             , quickCheckFailureReason = "Insufficient coverage"
             , quickCheckFailureCounterexample = [
-                " 0.8% is 23"
+                " 0.9% is 23"
               , ""
-              , "Only 0.8% is 23, but expected 10.0%"
+              , "Only 0.9% is 23, but expected 10.0%"
               ]
             }
 
         it "parses result" $ do
           parseQuickCheckResult <$> qc p `shouldReturn`
-            QuickCheckResult 400 "" (QuickCheckFailure failure)
+            QuickCheckResult 800 "" (QuickCheckFailure failure)
 
         it "includes verbose output" $ do
-          let info = intercalate "\n\n" (replicate 399 "Passed:")
+          let info = intercalate "\n\n" (replicate 799 "Passed:")
           parseQuickCheckResult <$> qc (verbose . p) `shouldReturn`
-            QuickCheckResult 400 info (QuickCheckFailure failure)
+            QuickCheckResult 800 info (QuickCheckFailure failure)
 
     context "with Failure" $ do
       context "with single-line failure reason" $ do
@@ -155,7 +155,7 @@
           p = (< 1)
 
           err = "Falsified"
-          result = QuickCheckResult 3 "" (QuickCheckFailure $ QCFailure 1 
Nothing err ["1"])
+          result = QuickCheckResult 4 "" (QuickCheckFailure $ QCFailure 2 
Nothing err ["1"])
 
         it "parses result" $ do
           parseQuickCheckResult <$> qc p `shouldReturn` result
@@ -166,7 +166,16 @@
                 , "0"
                 , ""
                 , "Passed:"
-                , "-1"
+                , "0"
+                , ""
+                , "Passed:"
+                , "-2"
+                , ""
+                , "Failed:"
+                , "3"
+                , ""
+                , "Passed:"
+                , "0"
                 , ""
                 , "Failed:"
                 , "2"
@@ -189,7 +198,7 @@
           p n = if n /= 2 then QCP.succeeded else QCP.failed {QCP.reason = err}
 
           err = "foo\nbar"
-          result = QuickCheckResult 3 "" (QuickCheckFailure $ QCFailure 0 
Nothing err ["2"])
+          result = QuickCheckResult 5 "" (QuickCheckFailure $ QCFailure 0 
Nothing err ["2"])
 
         it "parses result" $ do
           parseQuickCheckResult <$> qc p `shouldReturn` result
@@ -200,7 +209,13 @@
                 , "0"
                 , ""
                 , "Passed:"
-                , "-1"
+                , "0"
+                , ""
+                , "Passed:"
+                , "-2"
+                , ""
+                , "Passed:"
+                , "3"
                 , ""
                 , "Failed:"
                 , "2"
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/test/Test/Hspec/Core/RunnerSpec.hs 
new/hspec-core-2.7.4/test/Test/Hspec/Core/RunnerSpec.hs
--- old/hspec-core-2.7.1/test/Test/Hspec/Core/RunnerSpec.hs     2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/test/Test/Hspec/Core/RunnerSpec.hs     2020-09-01 
14:11:21.000000000 +0200
@@ -285,6 +285,14 @@
           , ""
           , "  To rerun use: --match \"/bar/\""
           , ""
+#if __GLASGOW_HASKELL__ == 800
+          , "WARNING:"
+          , "  Your version of GHC is affected by 
https://ghc.haskell.org/trac/ghc/ticket/13285.";
+          , "  Source locations may not work as expected."
+          , ""
+          , "  Please consider upgrading GHC!"
+          , ""
+#endif
           , "Randomized with seed 23"
           , ""
           , "Finished in 0.0000 seconds"
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/test/Test/Hspec/Core/ShuffleSpec.hs 
new/hspec-core-2.7.4/test/Test/Hspec/Core/ShuffleSpec.hs
--- old/hspec-core-2.7.1/test/Test/Hspec/Core/ShuffleSpec.hs    1970-01-01 
01:00:00.000000000 +0100
+++ new/hspec-core-2.7.4/test/Test/Hspec/Core/ShuffleSpec.hs    2020-09-01 
14:11:21.000000000 +0200
@@ -0,0 +1,47 @@
+module Test.Hspec.Core.ShuffleSpec (spec) where
+
+import           Prelude ()
+import           Helper
+
+import qualified Test.Hspec.Core.Shuffle as H
+import           Test.Hspec.Core.Tree
+
+import           Data.Array.ST
+import           Control.Monad.ST
+import           Data.STRef
+import           System.Random
+
+spec :: Spec
+spec = do
+  describe "shuffleForest" $ do
+    let
+      shuffleForest :: Int -> [Tree () Int] -> [Tree () Int]
+      shuffleForest seed xs = runST $ do
+        gen <- newSTRef (mkStdGen seed)
+        H.shuffleForest gen xs
+
+    it "shuffles a forest" $ do
+      shuffleForest 2
+        [Leaf 1, Leaf 2, Leaf 3] `shouldBe`
+        [Leaf 3, Leaf 1, Leaf 2]
+
+    it "recurses into Node" $ do
+      shuffleForest 1
+        [Node "foo" [Node "bar" [Leaf 1, Leaf 2, Leaf 3]]] `shouldBe`
+        [Node "foo" [Node "bar" [Leaf 2, Leaf 3, Leaf 1]]]
+
+    it "recurses into NodeWithCleanup" $ do
+      shuffleForest 1
+        [NodeWithCleanup () [NodeWithCleanup () [Leaf 1, Leaf 2, Leaf 3]]] 
`shouldBe`
+        [NodeWithCleanup () [NodeWithCleanup () [Leaf 2, Leaf 3, Leaf 1]]]
+
+  describe "shuffle" $ do
+    it "shuffles a list" $ do
+      runST $ do
+        gen <- newSTRef (mkStdGen 2)
+        H.shuffle gen [1, 2, 3 :: Int]
+      `shouldBe` [3, 1, 2]
+
+  describe "mkArray" $ do
+    it "creates an STArray from a list" $ do
+      runST (H.mkArray [1, 2, 3 :: Int] >>= getElems) `shouldBe` [1, 2, 3]
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/hspec-core-2.7.1/vendor/Control/Concurrent/Async.hs 
new/hspec-core-2.7.4/vendor/Control/Concurrent/Async.hs
--- old/hspec-core-2.7.1/vendor/Control/Concurrent/Async.hs     2019-03-29 
13:56:43.000000000 +0100
+++ new/hspec-core-2.7.4/vendor/Control/Concurrent/Async.hs     2020-09-01 
14:11:21.000000000 +0200
@@ -146,7 +146,7 @@
 #if __GLASGOW_HASKELL__ < 710
 import Data.Typeable
 #endif
-#if MIN_VERSION_base(4,9,0)
+#if MIN_VERSION_base(4,9,0) && !MIN_VERSION_base(4,13,0)
 import Data.Semigroup (Semigroup((<>)))
 #endif
 


Reply via email to