[commit: packages/containers] cleaned_bugfix394, master, merge-doc-target, merge-fixes-5.9, merge-restrict-fix-5.8, revert-408-bugfix_394: Remove unnecessary extensions from tests (db430be)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:42:18 UTC 2017


Repository : ssh://git@git.haskell.org/containers

On branches: cleaned_bugfix394,master,merge-doc-target,merge-fixes-5.9,merge-restrict-fix-5.8,revert-408-bugfix_394
Link       : http://git.haskell.org/packages/containers.git/commitdiff/db430beb2287f7db34975bc25c3e0ac759db5b39

>---------------------------------------------------------------

commit db430beb2287f7db34975bc25c3e0ac759db5b39
Author: David Feuer <David.Feuer at gmail.com>
Date:   Tue May 24 02:03:13 2016 -0400

    Remove unnecessary extensions from tests
    
    Use `Text.Show.Functions` (blech!) to avoid declaring our own,
    similar instances and using `FlexibleInstances` to do so (double
    blech!). Remove unused invocation of `GeneralizedNewtypeDeriving`.


>---------------------------------------------------------------

db430beb2287f7db34975bc25c3e0ac759db5b39
 tests/bitqueue-properties.hs |  1 -
 tests/intmap-strictness.hs   | 12 ++----------
 tests/intset-strictness.hs   |  3 ---
 tests/map-strictness.hs      | 12 ++----------
 4 files changed, 4 insertions(+), 24 deletions(-)

diff --git a/tests/bitqueue-properties.hs b/tests/bitqueue-properties.hs
index c533839..06ab54a 100644
--- a/tests/bitqueue-properties.hs
+++ b/tests/bitqueue-properties.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE CPP #-}
 {-# LANGUAGE BangPatterns #-}
-{-# OPTIONS_GHC -Wall #-}
 
 #if !MIN_VERSION_base(4,8,0)
 import Control.Applicative ((<$>))
diff --git a/tests/intmap-strictness.hs b/tests/intmap-strictness.hs
index bae93ac..7dc9d3a 100644
--- a/tests/intmap-strictness.hs
+++ b/tests/intmap-strictness.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
 module Main (main) where
@@ -8,21 +7,14 @@ import Test.Framework (Test, defaultMain, testGroup)
 import Test.Framework.Providers.QuickCheck2 (testProperty)
 import Test.QuickCheck (Arbitrary(arbitrary))
 
+import Text.Show.Functions ()
+
 import Data.IntMap.Strict (IntMap)
 import qualified Data.IntMap.Strict as M
 
 instance Arbitrary v => Arbitrary (IntMap v) where
     arbitrary = M.fromList `fmap` arbitrary
 
-instance Show (Int -> Int) where
-    show _ = "<function>"
-
-instance Show (Int -> Int -> Int) where
-    show _ = "<function>"
-
-instance Show (Int -> Int -> Int -> Int) where
-    show _ = "<function>"
-
 ------------------------------------------------------------------------
 -- * Properties
 
diff --git a/tests/intset-strictness.hs b/tests/intset-strictness.hs
index b7c4097..c31aca1 100644
--- a/tests/intset-strictness.hs
+++ b/tests/intset-strictness.hs
@@ -1,6 +1,3 @@
-{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving #-}
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-
 module Main (main) where
 
 import Prelude hiding (foldl)
diff --git a/tests/map-strictness.hs b/tests/map-strictness.hs
index ab28757..c5ef8bc 100644
--- a/tests/map-strictness.hs
+++ b/tests/map-strictness.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
 module Main (main) where
@@ -8,6 +7,8 @@ import Test.Framework (Test, defaultMain, testGroup)
 import Test.Framework.Providers.QuickCheck2 (testProperty)
 import Test.QuickCheck (Arbitrary(arbitrary))
 
+import Text.Show.Functions ()
+
 import Data.Map.Strict (Map)
 import qualified Data.Map.Strict as M
 
@@ -15,15 +16,6 @@ instance (Arbitrary k, Arbitrary v, Ord k) =>
          Arbitrary (Map k v) where
     arbitrary = M.fromList `fmap` arbitrary
 
-instance Show (Int -> Int) where
-    show _ = "<function>"
-
-instance Show (Int -> Int -> Int) where
-    show _ = "<function>"
-
-instance Show (Int -> Int -> Int -> Int) where
-    show _ = "<function>"
-
 ------------------------------------------------------------------------
 -- * Properties
 



More information about the ghc-commits mailing list