diff options
author | Herbert Valerio Riedel <hvr@gnu.org> | 2014-09-15 08:37:30 +0200 |
---|---|---|
committer | Herbert Valerio Riedel <hvr@gnu.org> | 2014-09-15 08:37:39 +0200 |
commit | c0fa383d9109800a4e46a81b418f1794030ba1bd (patch) | |
tree | 19dc80e4d266eb6fd7b56b6f61d4f7ed4f10a097 | |
parent | 004c5f4fec78414943d788c2a8b42a4500272949 (diff) | |
download | haskell-c0fa383d9109800a4e46a81b418f1794030ba1bd.tar.gz |
Export `Traversable()` and `Foldable()` from Prelude
This exposes *only* the type-classes w/o any of their methods.
This is the very first step for implementing BPP (see #9586), which
already requires breaking up several import-cycles leading back to `Prelude`.
Ideally, importing `Prelude` should be avoided in most `base` modules,
as `Prelude` does not define any entities, but rather re-exports
existing ones.
Test Plan: validate passes
Reviewers: ekmett, austin
Reviewed By: ekmett, austin
Subscribers: simonmar, ezyang, carter
Differential Revision: https://phabricator.haskell.org/D209
GHC Trac Issues: #9586
-rw-r--r-- | compiler/hsSyn/HsDecls.lhs | 7 | ||||
-rw-r--r-- | compiler/utils/BooleanFormula.hs | 4 | ||||
-rw-r--r-- | libraries/base/Control/Applicative.hs | 17 | ||||
-rw-r--r-- | libraries/base/Control/Arrow.hs | 6 | ||||
-rw-r--r-- | libraries/base/Control/Category.hs | 7 | ||||
-rw-r--r-- | libraries/base/Control/Monad/Fix.hs | 11 | ||||
-rw-r--r-- | libraries/base/Data/Data.hs | 19 | ||||
-rw-r--r-- | libraries/base/Data/Foldable.hs | 37 | ||||
-rw-r--r-- | libraries/base/Data/Function.hs | 5 | ||||
-rw-r--r-- | libraries/base/Data/Functor.hs | 3 | ||||
-rw-r--r-- | libraries/base/Data/Traversable.hs | 18 | ||||
-rw-r--r-- | libraries/base/Data/Version.hs | 20 | ||||
-rw-r--r-- | libraries/base/Debug/Trace.hs | 6 | ||||
-rwxr-xr-x | libraries/base/GHC/Exts.hs | 6 | ||||
-rw-r--r-- | libraries/base/GHC/Stack.hsc | 5 | ||||
-rw-r--r-- | libraries/base/Prelude.hs | 5 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T4175.stdout | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/T7627.stdout | 2 | ||||
-rw-r--r-- | testsuite/tests/ghci/scripts/ghci011.stdout | 4 | ||||
-rw-r--r-- | testsuite/tests/perf/compiler/all.T | 9 | ||||
-rw-r--r-- | testsuite/tests/typecheck/should_compile/FD2.stderr | 4 |
21 files changed, 131 insertions, 66 deletions
diff --git a/compiler/hsSyn/HsDecls.lhs b/compiler/hsSyn/HsDecls.lhs index f584372385..3d412874fd 100644 --- a/compiler/hsSyn/HsDecls.lhs +++ b/compiler/hsSyn/HsDecls.lhs @@ -4,6 +4,7 @@ % \begin{code} +{-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable, DeriveFunctor, DeriveFoldable, DeriveTraversable #-} {-# LANGUAGE StandaloneDeriving #-} @@ -98,8 +99,10 @@ import FastString import Bag import Data.Data hiding (TyCon,Fixity) -import Data.Foldable (Foldable) -import Data.Traversable +#if __GLASGOW_HASKELL__ < 709 +import Data.Foldable ( Foldable ) +import Data.Traversable ( Traversable ) +#endif import Data.Maybe \end{code} diff --git a/compiler/utils/BooleanFormula.hs b/compiler/utils/BooleanFormula.hs index 8620ef555d..5925bdb758 100644 --- a/compiler/utils/BooleanFormula.hs +++ b/compiler/utils/BooleanFormula.hs @@ -1,3 +1,5 @@ +{-# LANGUAGE CPP #-} + -------------------------------------------------------------------------------- -- | Boolean formulas without quantifiers and without negation. -- Such a formula consists of variables, conjunctions (and), and disjunctions (or). @@ -18,8 +20,10 @@ module BooleanFormula ( import Data.List ( nub, intersperse ) import Data.Data +#if __GLASGOW_HASKELL__ < 709 import Data.Foldable ( Foldable ) import Data.Traversable ( Traversable ) +#endif import MonadUtils import Outputable diff --git a/libraries/base/Control/Applicative.hs b/libraries/base/Control/Applicative.hs index 41049c6a9f..7bab7294fb 100644 --- a/libraries/base/Control/Applicative.hs +++ b/libraries/base/Control/Applicative.hs @@ -1,6 +1,7 @@ -{-# LANGUAGE Trustworthy #-} {-# LANGUAGE AutoDeriveTypeable #-} {-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -46,16 +47,22 @@ module Control.Applicative ( optional, ) where -import Prelude hiding (id,(.)) - -import GHC.Base (liftA, liftA2, liftA3, (<**>)) import Control.Category import Control.Arrow -import Control.Monad (liftM, ap, MonadPlus(..), Alternative(..)) +import Control.Monad (liftM, ap, Monad(..), MonadPlus(..), Alternative(..)) import Data.Functor ((<$>), (<$)) +import Data.Maybe import Data.Monoid (Monoid(..)) +import Data.Tuple +import Data.Eq +import Data.Ord +import Data.Functor (Functor(..)) +import GHC.Base (const, Applicative(..),liftA, liftA2, liftA3, (<**>)) import GHC.Generics +import GHC.List (map, repeat, zipWith) +import GHC.Read (Read) +import GHC.Show (Show) newtype Const a b = Const { getConst :: a } deriving (Generic, Generic1) diff --git a/libraries/base/Control/Arrow.hs b/libraries/base/Control/Arrow.hs index f6067a01c3..0efaa87e69 100644 --- a/libraries/base/Control/Arrow.hs +++ b/libraries/base/Control/Arrow.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -41,11 +42,12 @@ module Control.Arrow ( ArrowLoop(..) ) where -import Prelude hiding (id,(.)) - +import Data.Tuple ( fst, snd, uncurry ) +import Data.Either import Control.Monad import Control.Monad.Fix import Control.Category +import GHC.Base ( Applicative(..), const, ($) ) infixr 5 <+> infixr 3 *** diff --git a/libraries/base/Control/Category.hs b/libraries/base/Control/Category.hs index 3b8dc2b5ce..22166477e6 100644 --- a/libraries/base/Control/Category.hs +++ b/libraries/base/Control/Category.hs @@ -1,4 +1,5 @@ {-# LANGUAGE GADTs #-} +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE Trustworthy #-} @@ -16,7 +17,7 @@ module Control.Category where -import qualified Prelude +import qualified GHC.Base (id,(.)) import Data.Type.Coercion import Data.Type.Equality import GHC.Prim (coerce) @@ -43,8 +44,8 @@ class Category cat where #-} instance Category (->) where - id = Prelude.id - (.) = (Prelude..) + id = GHC.Base.id + (.) = (GHC.Base..) instance Category (:~:) where id = Refl diff --git a/libraries/base/Control/Monad/Fix.hs b/libraries/base/Control/Monad/Fix.hs index 8036fefcd1..56e249c746 100644 --- a/libraries/base/Control/Monad/Fix.hs +++ b/libraries/base/Control/Monad/Fix.hs @@ -1,4 +1,5 @@ {-# LANGUAGE Trustworthy #-} +{-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | @@ -22,10 +23,14 @@ module Control.Monad.Fix ( fix ) where -import Prelude -import System.IO -import Data.Function (fix) +import Control.Monad ( Monad ) +import Data.Either +import Data.Function ( fix ) +import Data.Maybe +import GHC.Base ( error, (.) ) +import GHC.List ( head, tail ) import GHC.ST +import System.IO -- | Monads having fixed points with a \'knot-tying\' semantics. -- Instances of 'MonadFix' should satisfy the following laws: diff --git a/libraries/base/Data/Data.hs b/libraries/base/Data/Data.hs index 095bca119f..8407c6f1ba 100644 --- a/libraries/base/Data/Data.hs +++ b/libraries/base/Data/Data.hs @@ -2,6 +2,7 @@ {-# LANGUAGE RankNTypes, ScopedTypeVariables, PolyKinds #-} {-# LANGUAGE StandaloneDeriving, AutoDeriveTypeable, TypeOperators, GADTs #-} +{-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | @@ -106,19 +107,25 @@ module Data.Data ( ------------------------------------------------------------------------------ -import Prelude -- necessary to get dependencies right - -import Data.Typeable +import Control.Monad +import Data.Either +import Data.Eq import Data.Maybe +import Data.Ord +import Data.Typeable import Data.Version( Version(..) ) -import Control.Monad +import GHC.Base +import GHC.List +import GHC.Num +import GHC.Read +import GHC.Show +import Text.Read( reads ) -- Imports for the instances import Data.Int -- So we can give Data instance for Int8, ... import Data.Type.Coercion -import Data.Coerce import Data.Word -- So we can give Data instance for Word8, ... -import GHC.Real( Ratio(..) ) -- So we can give Data instance for Ratio +import GHC.Real -- So we can give Data instance for Ratio --import GHC.IOBase -- So we can give Data instance for IO, Handle import GHC.Ptr -- So we can give Data instance for Ptr import GHC.ForeignPtr -- So we can give Data instance for ForeignPtr diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index 0f0d5bfbf1..4e6681a542 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- @@ -57,19 +58,21 @@ module Data.Foldable ( find ) where -import Prelude hiding (foldl, foldr, foldl1, foldr1, mapM_, sequence_, - elem, notElem, concat, concatMap, and, or, any, all, - sum, product, maximum, minimum) -import qualified Prelude (foldl, foldr, foldl1, foldr1) -import qualified Data.List as List (foldl') import Control.Applicative -import Control.Monad (MonadPlus(..)) -import Data.Maybe (fromMaybe, listToMaybe) +import Control.Monad ( Monad(..), MonadPlus(..) ) +import Data.Bool +import Data.Either +import Data.Eq +import qualified Data.List as List +import Data.Maybe import Data.Monoid +import Data.Ord import Data.Proxy -import GHC.Exts (build) -import GHC.Arr +import GHC.Arr ( Array(..), Ix(..), elems ) +import GHC.Base ( (.), ($!), error, flip, id ) +import GHC.Exts ( build ) +import GHC.Num ( Num(..) ) -- | Data structures that can be folded. -- @@ -163,11 +166,11 @@ instance Foldable Maybe where foldl f z (Just x) = f z x instance Foldable [] where - foldr = Prelude.foldr - foldl = Prelude.foldl + foldr = List.foldr + foldl = List.foldl foldl' = List.foldl' - foldr1 = Prelude.foldr1 - foldl1 = Prelude.foldl1 + foldr1 = List.foldr1 + foldl1 = List.foldl1 instance Foldable (Either a) where foldMap _ (Left _) = mempty @@ -182,10 +185,10 @@ instance Foldable ((,) a) where foldr f z (_, y) = f y z instance Ix i => Foldable (Array i) where - foldr f z = Prelude.foldr f z . elems - foldl f z = Prelude.foldl f z . elems - foldr1 f = Prelude.foldr1 f . elems - foldl1 f = Prelude.foldl1 f . elems + foldr f z = List.foldr f z . elems + foldl f z = List.foldl f z . elems + foldr1 f = List.foldr1 f . elems + foldl1 f = List.foldl1 f . elems instance Foldable Proxy where foldMap _ _ = mempty diff --git a/libraries/base/Data/Function.hs b/libraries/base/Data/Function.hs index a3fac7ca4d..81ab2224c1 100644 --- a/libraries/base/Data/Function.hs +++ b/libraries/base/Data/Function.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE Safe #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -24,7 +25,7 @@ module Data.Function , on ) where -import Prelude +import GHC.Base ( ($), (.), id, const, flip ) infixl 0 `on` infixl 1 & diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 1869b1604a..f769d52446 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- @@ -23,7 +24,7 @@ module Data.Functor ) where import Control.Monad -import GHC.Base (Functor(..)) +import GHC.Base ( Functor(..), flip ) infixl 4 <$> diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs index e69d2b3c5a..19e9d477e6 100644 --- a/libraries/base/Data/Traversable.hs +++ b/libraries/base/Data/Traversable.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- @@ -50,14 +51,19 @@ module Data.Traversable ( foldMapDefault, ) where -import Prelude hiding (mapM, sequence, foldr) -import qualified Prelude (mapM, foldr) import Control.Applicative -import Data.Foldable (Foldable()) -import Data.Monoid (Monoid) +import Control.Monad ( Monad(..) ) +import qualified Control.Monad +import Data.Either +import Data.Foldable ( Foldable ) +import Data.Functor +import Data.Maybe +import Data.Monoid ( Monoid ) import Data.Proxy import GHC.Arr +import GHC.Base ( ($), (.), id, flip ) +import qualified GHC.List as List -- | Functors representing data structures that can be traversed from -- left to right. @@ -174,10 +180,10 @@ instance Traversable Maybe where instance Traversable [] where {-# INLINE traverse #-} -- so that traverse can fuse - traverse f = Prelude.foldr cons_f (pure []) + traverse f = List.foldr cons_f (pure []) where cons_f x ys = (:) <$> f x <*> ys - mapM = Prelude.mapM + mapM = Control.Monad.mapM instance Traversable (Either a) where traverse _ (Left x) = pure (Left x) diff --git a/libraries/base/Data/Version.hs b/libraries/base/Data/Version.hs index 8b88486571..adc0f125b5 100644 --- a/libraries/base/Data/Version.hs +++ b/libraries/base/Data/Version.hs @@ -1,5 +1,6 @@ -{-# LANGUAGE Trustworthy #-} {-# LANGUAGE AutoDeriveTypeable #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE Trustworthy #-} ----------------------------------------------------------------------------- -- | @@ -33,14 +34,17 @@ module Data.Version ( showVersion, parseVersion, ) where -import Prelude -- necessary to get dependencies right - -import Text.ParserCombinators.ReadP - -import Data.Typeable ( Typeable ) -import Data.List ( intersperse, sort ) -import Control.Monad ( liftM ) +import Control.Monad ( Monad(..), liftM ) import Data.Char ( isDigit, isAlphaNum ) +import Data.Eq +import Data.List +import Data.Ord +import Data.Typeable ( Typeable ) +import GHC.Base ( ($), (&&), String, Int ) +import GHC.Read +import GHC.Show +import Text.ParserCombinators.ReadP +import Text.Read ( read ) {- | A 'Version' represents the version of a software entity. diff --git a/libraries/base/Debug/Trace.hs b/libraries/base/Debug/Trace.hs index 92e5b205c8..9705e29fdc 100644 --- a/libraries/base/Debug/Trace.hs +++ b/libraries/base/Debug/Trace.hs @@ -1,5 +1,7 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE Unsafe #-} -{-# LANGUAGE MagicHash, UnboxedTuples #-} ----------------------------------------------------------------------------- -- | @@ -42,7 +44,6 @@ module Debug.Trace ( traceMarkerIO, ) where -import Prelude import System.IO.Unsafe import Control.Monad @@ -51,6 +52,7 @@ import GHC.Base import qualified GHC.Foreign import GHC.IO.Encoding import GHC.Ptr +import GHC.Show import GHC.Stack import Data.List diff --git a/libraries/base/GHC/Exts.hs b/libraries/base/GHC/Exts.hs index 938631001a..6499da878a 100755 --- a/libraries/base/GHC/Exts.hs +++ b/libraries/base/GHC/Exts.hs @@ -1,5 +1,6 @@ {-# LANGUAGE Unsafe #-} {-# LANGUAGE MagicHash, UnboxedTuples, AutoDeriveTypeable, TypeFamilies, MultiParamTypeClasses, FlexibleInstances #-} +{-# LANGUAGE NoImplicitPrelude #-} ----------------------------------------------------------------------------- -- | @@ -71,14 +72,13 @@ module GHC.Exts IsList(..) ) where -import Prelude - -import GHC.Prim hiding (coerce) +import GHC.Prim hiding (coerce, Constraint) import GHC.Base hiding (coerce) -- implicitly comes from GHC.Prim import GHC.Word import GHC.Int import GHC.Ptr import GHC.Stack + import qualified Data.Coerce import Data.String import Data.List diff --git a/libraries/base/GHC/Stack.hsc b/libraries/base/GHC/Stack.hsc index 079f5b0516..0b30391cdc 100644 --- a/libraries/base/GHC/Stack.hsc +++ b/libraries/base/GHC/Stack.hsc @@ -13,7 +13,7 @@ -- /Since: 4.5.0.0/ ----------------------------------------------------------------------------- -{-# LANGUAGE UnboxedTuples, MagicHash #-} +{-# LANGUAGE UnboxedTuples, MagicHash, NoImplicitPrelude #-} module GHC.Stack ( -- * Call stack currentCallStack, @@ -34,6 +34,8 @@ module GHC.Stack ( renderStack ) where +import Control.Monad ( (=<<) ) + import Foreign import Foreign.C @@ -43,6 +45,7 @@ import GHC.Ptr import GHC.Foreign as GHC import GHC.IO.Encoding import GHC.Exception +import GHC.List ( concatMap, null, reverse ) #define PROFILING #include "Rts.h" diff --git a/libraries/base/Prelude.hs b/libraries/base/Prelude.hs index f58cd17cd2..53414c95dc 100644 --- a/libraries/base/Prelude.hs +++ b/libraries/base/Prelude.hs @@ -72,6 +72,9 @@ module Prelude ( Monad((>>=), (>>), return, fail), mapM, mapM_, sequence, sequence_, (=<<), + -- ** Traversals and Foldables + Foldable, Traversable, + -- ** Miscellaneous functions id, const, (.), flip, ($), until, asTypeOf, error, undefined, @@ -140,7 +143,9 @@ import System.IO import System.IO.Error import Data.List import Data.Either +import Data.Foldable ( Foldable ) import Data.Maybe +import Data.Traversable ( Traversable ) import Data.Tuple import GHC.Base diff --git a/testsuite/tests/ghci/scripts/T4175.stdout b/testsuite/tests/ghci/scripts/T4175.stdout index 0cf5e9b5c0..2a75b0da6a 100644 --- a/testsuite/tests/ghci/scripts/T4175.stdout +++ b/testsuite/tests/ghci/scripts/T4175.stdout @@ -36,6 +36,8 @@ instance Ord a => Ord (Maybe a) -- Defined in ‘Data.Maybe’ instance Read a => Read (Maybe a) -- Defined in ‘GHC.Read’ instance Show a => Show (Maybe a) -- Defined in ‘GHC.Show’ instance Applicative Maybe -- Defined in ‘Data.Maybe’ +instance Foldable Maybe -- Defined in ‘Data.Foldable’ +instance Traversable Maybe -- Defined in ‘Data.Traversable’ type instance A (Maybe a) a = a -- Defined at T4175.hs:9:1 data Int = I# Int# -- Defined in ‘GHC.Types’ instance C Int -- Defined at T4175.hs:18:10 diff --git a/testsuite/tests/ghci/scripts/T7627.stdout b/testsuite/tests/ghci/scripts/T7627.stdout index 9177bbd1e1..451c7051df 100644 --- a/testsuite/tests/ghci/scripts/T7627.stdout +++ b/testsuite/tests/ghci/scripts/T7627.stdout @@ -20,6 +20,8 @@ instance (Read a, Read b) => Read (a, b) -- Defined in ‘GHC.Read’ instance (Show a, Show b) => Show (a, b) -- Defined in ‘GHC.Show’ instance GHC.Base.Monoid a => Applicative ((,) a) -- Defined in ‘GHC.Base’ +instance Foldable ((,) a) -- Defined in ‘Data.Foldable’ +instance Traversable ((,) a) -- Defined in ‘Data.Traversable’ data (#,#) (a :: OpenKind) (b :: OpenKind) = (#,#) a b -- Defined in ‘GHC.Prim’ (,) :: a -> b -> (a, b) diff --git a/testsuite/tests/ghci/scripts/ghci011.stdout b/testsuite/tests/ghci/scripts/ghci011.stdout index 6b807f65c2..0563b83e66 100644 --- a/testsuite/tests/ghci/scripts/ghci011.stdout +++ b/testsuite/tests/ghci/scripts/ghci011.stdout @@ -6,6 +6,8 @@ instance Ord a => Ord [a] -- Defined in ‘GHC.Classes’ instance Read a => Read [a] -- Defined in ‘GHC.Read’ instance Show a => Show [a] -- Defined in ‘GHC.Show’ instance Applicative [] -- Defined in ‘GHC.Base’ +instance Foldable [] -- Defined in ‘Data.Foldable’ +instance Traversable [] -- Defined in ‘Data.Traversable’ data () = () -- Defined in ‘GHC.Tuple’ instance Bounded () -- Defined in ‘GHC.Enum’ instance Enum () -- Defined in ‘GHC.Enum’ @@ -23,3 +25,5 @@ instance (Read a, Read b) => Read (a, b) -- Defined in ‘GHC.Read’ instance (Show a, Show b) => Show (a, b) -- Defined in ‘GHC.Show’ instance GHC.Base.Monoid a => Applicative ((,) a) -- Defined in ‘GHC.Base’ +instance Foldable ((,) a) -- Defined in ‘Data.Foldable’ +instance Traversable ((,) a) -- Defined in ‘Data.Traversable’ diff --git a/testsuite/tests/perf/compiler/all.T b/testsuite/tests/perf/compiler/all.T index f71204f2d5..be09a1c6d0 100644 --- a/testsuite/tests/perf/compiler/all.T +++ b/testsuite/tests/perf/compiler/all.T @@ -246,7 +246,7 @@ test('T3064', # 2012-10-30: 111189536 (x86/Windows) # 2013-11-13: 146626504 (x86/Windows, 64bit machine) # 2014-01-22: 162457940 (x86/Linux) - (wordsize(64), 407416464, 5)]), + (wordsize(64), 385145080, 5)]), # (amd64/Linux) (28/06/2011): 73259544 # (amd64/Linux) (07/02/2013): 224798696 # (amd64/Linux) (02/08/2013): 236404384, increase from roles @@ -258,6 +258,7 @@ test('T3064', # (amd64/Linux) (2014-07-17): 332702112, general round of updates # (amd64/Linux) (2014-08-29): 313638592, w/w for INLINABLE things # (amd64/Linux) (09/09/2014): 407416464, AMP changes (larger interfaces, more loading) + # (amd64/Linux) (14/09/2014): 385145080, BPP changes (more NoImplicitPrelude in base) compiler_stats_num_field('max_bytes_used', [(wordsize(32), 11202304, 20), @@ -265,7 +266,7 @@ test('T3064', #(some date): 5511604 # 2013-11-13: 7218200 (x86/Windows, 64bit machine) # 2014-04-04: 11202304 (x86/Windows, 64bit machine) - (wordsize(64), 24357392, 20)]), + (wordsize(64), 16053888, 20)]), # (amd64/Linux, intree) (28/06/2011): 4032024 # (amd64/Linux, intree) (07/02/2013): 9819288 # (amd64/Linux) (14/02/2013): 8687360 @@ -277,6 +278,7 @@ test('T3064', # (amd64/Linux) (22/11/2013): 16266992, GND via Coercible and counters for constraints solving # (amd64/Linux) (12/12/2013): 19821544, better One shot analysis # (amd64/Linux) (09/09/2014): 24357392, AMP changes (larger interfaces, more loading) + # (amd64/Linux) (14/09/2014): 16053888, BPP changes (more NoImplicitPrelude in base) only_ways(['normal']) ], compile, @@ -456,7 +458,7 @@ test('T6048', # 2012-10-08: 48887164 (x86/Linux) # 2014-04-04: 62618072 (x86 Windows, 64 bit machine) # 2014-09-03: 56315812 (x86 Windows, w/w for INLINEAVBLE) - (wordsize(64), 108354472, 12)]) + (wordsize(64), 88186056, 12)]) # 18/09/2012 97247032 amd64/Linux # 16/01/2014 108578664 amd64/Linux (unknown, likely foldl-via-foldr) # 18/01/2014 95960720 amd64/Linux Call Arity improvements @@ -464,6 +466,7 @@ test('T6048', # 05/03/2014 110646312 amd64/Linux Call Arity became more elaborate # 14/07/2014 125431448 amd64/Linux unknown reason. Even worse in GHC-7.8.3. *shurg* # 29/08/2014 108354472 amd64/Linux w/w for INLINABLE things + # 14/09/2014 88186056 amd64/Linux BPP part1 change (more NoImplicitPreludes in base) ], compile,['']) diff --git a/testsuite/tests/typecheck/should_compile/FD2.stderr b/testsuite/tests/typecheck/should_compile/FD2.stderr index 06e5afd730..691d5b5b84 100644 --- a/testsuite/tests/typecheck/should_compile/FD2.stderr +++ b/testsuite/tests/typecheck/should_compile/FD2.stderr @@ -1,8 +1,8 @@ FD2.hs:26:34: Could not deduce (e ~ e1) - from the context (Foldable a) - bound by the class declaration for ‘Foldable’ + from the context (ShouldCompile.Foldable a) + bound by the class declaration for ‘ShouldCompile.Foldable’ at FD2.hs:(17,1)-(26,39) or from (Elem a e) bound by the type signature for |