summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2016-07-18 15:54:16 +0200
committerBen Gamari <ben@smart-cactus.org>2016-07-18 15:54:16 +0200
commitcb12bdf942df5e61771d69bbb6049f3b23ed580c (patch)
tree1fbc5302c01af8ab71b3d662121d9354de75bde4
parent8e1e52ffd0b05bd1f865ce0421a4cae957bf41a5 (diff)
downloadhaskell-wip/generics-flip.tar.gz
Flip around imports of GHC.Genericswip/generics-flip
Previously we had, GHC.Generics imports GHC.Ptr Data.Monoid imports GHC.Generics Data.Foldable imports GHC.Generics Data.Foldable imports Data.Monoid Prelude imports Data.Foldable Unfortunately this meant that any program importing Prelude (essentially all programs) would end up pulling in GHC.Generics and GHC.Ptr unnecessarily. Hopefully helps #12367.
-rw-r--r--libraries/base/Data/Foldable.hs36
-rw-r--r--libraries/base/Data/Monoid.hs19
-rw-r--r--libraries/base/GHC/Generics.hs67
3 files changed, 72 insertions, 50 deletions
diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs
index 6ad549f0fe..460ebde833 100644
--- a/libraries/base/Data/Foldable.hs
+++ b/libraries/base/Data/Foldable.hs
@@ -2,7 +2,6 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeOperators #-}
@@ -66,7 +65,6 @@ import GHC.Arr ( Array(..), elems, numElements,
foldlElems', foldrElems',
foldl1Elems, foldr1Elems)
import GHC.Base hiding ( foldr )
-import GHC.Generics
import GHC.Num ( Num(..) )
infix 4 `elem`, `notElem`
@@ -407,40 +405,6 @@ instance Foldable First where
instance Foldable Last where
foldMap f = foldMap f . getLast
--- Instances for GHC.Generics
--- | @since 4.9.0.0
-instance Foldable U1 where
- foldMap _ _ = mempty
- {-# INLINE foldMap #-}
- fold _ = mempty
- {-# INLINE fold #-}
- foldr _ z _ = z
- {-# INLINE foldr #-}
- foldl _ z _ = z
- {-# INLINE foldl #-}
- foldl1 _ _ = errorWithoutStackTrace "foldl1: U1"
- foldr1 _ _ = errorWithoutStackTrace "foldr1: U1"
- length _ = 0
- null _ = True
- elem _ _ = False
- sum _ = 0
- product _ = 1
-
-deriving instance Foldable V1
-deriving instance Foldable Par1
-deriving instance Foldable f => Foldable (Rec1 f)
-deriving instance Foldable (K1 i c)
-deriving instance Foldable f => Foldable (M1 i c f)
-deriving instance (Foldable f, Foldable g) => Foldable (f :+: g)
-deriving instance (Foldable f, Foldable g) => Foldable (f :*: g)
-deriving instance (Foldable f, Foldable g) => Foldable (f :.: g)
-deriving instance Foldable UAddr
-deriving instance Foldable UChar
-deriving instance Foldable UDouble
-deriving instance Foldable UFloat
-deriving instance Foldable UInt
-deriving instance Foldable UWord
-
-- | Monadic fold over the elements of a structure,
-- associating to the right, i.e. from right to left.
foldrM :: (Foldable t, Monad m) => (a -> b -> m b) -> b -> t a -> m b
diff --git a/libraries/base/Data/Monoid.hs b/libraries/base/Data/Monoid.hs
index 6ccdb34045..0087492b27 100644
--- a/libraries/base/Data/Monoid.hs
+++ b/libraries/base/Data/Monoid.hs
@@ -1,6 +1,5 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude #-}
-{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -47,7 +46,6 @@ import GHC.Enum
import GHC.Num
import GHC.Read
import GHC.Show
-import GHC.Generics
{-
-- just for testing
@@ -68,7 +66,7 @@ infixr 6 <>
-- | The dual of a 'Monoid', obtained by swapping the arguments of 'mappend'.
newtype Dual a = Dual { getDual :: a }
- deriving (Eq, Ord, Read, Show, Bounded, Generic, Generic1)
+ deriving (Eq, Ord, Read, Show, Bounded)
-- | @since 2.01
instance Monoid a => Monoid (Dual a) where
@@ -90,7 +88,6 @@ instance Monad Dual where
-- | The monoid of endomorphisms under composition.
newtype Endo a = Endo { appEndo :: a -> a }
- deriving (Generic)
-- | @since 2.01
instance Monoid (Endo a) where
@@ -99,7 +96,7 @@ instance Monoid (Endo a) where
-- | Boolean monoid under conjunction ('&&').
newtype All = All { getAll :: Bool }
- deriving (Eq, Ord, Read, Show, Bounded, Generic)
+ deriving (Eq, Ord, Read, Show, Bounded)
-- | @since 2.01
instance Monoid All where
@@ -108,7 +105,7 @@ instance Monoid All where
-- | Boolean monoid under disjunction ('||').
newtype Any = Any { getAny :: Bool }
- deriving (Eq, Ord, Read, Show, Bounded, Generic)
+ deriving (Eq, Ord, Read, Show, Bounded)
-- | @since 2.01
instance Monoid Any where
@@ -117,7 +114,7 @@ instance Monoid Any where
-- | Monoid under addition.
newtype Sum a = Sum { getSum :: a }
- deriving (Eq, Ord, Read, Show, Bounded, Generic, Generic1, Num)
+ deriving (Eq, Ord, Read, Show, Bounded, Num)
-- | @since 2.01
instance Num a => Monoid (Sum a) where
@@ -140,7 +137,7 @@ instance Monad Sum where
-- | Monoid under multiplication.
newtype Product a = Product { getProduct :: a }
- deriving (Eq, Ord, Read, Show, Bounded, Generic, Generic1, Num)
+ deriving (Eq, Ord, Read, Show, Bounded, Num)
-- | @since 2.01
instance Num a => Monoid (Product a) where
@@ -198,7 +195,7 @@ instance Monad Product where
-- @'First' a@ is isomorphic to @'Alt' 'Maybe' a@, but precedes it
-- historically.
newtype First a = First { getFirst :: Maybe a }
- deriving (Eq, Ord, Read, Show, Generic, Generic1,
+ deriving (Eq, Ord, Read, Show,
Functor, Applicative, Monad)
-- | @since 2.01
@@ -212,7 +209,7 @@ instance Monoid (First a) where
-- @'Last' a@ is isomorphic to @'Dual' ('First' a)@, and thus to
-- @'Dual' ('Alt' 'Maybe' a)@
newtype Last a = Last { getLast :: Maybe a }
- deriving (Eq, Ord, Read, Show, Generic, Generic1,
+ deriving (Eq, Ord, Read, Show,
Functor, Applicative, Monad)
-- | @since 2.01
@@ -225,7 +222,7 @@ instance Monoid (Last a) where
--
-- @since 4.8.0.0
newtype Alt f a = Alt {getAlt :: f a}
- deriving (Generic, Generic1, Read, Show, Eq, Ord, Num, Enum,
+ deriving (Read, Show, Eq, Ord, Num, Enum,
Monad, MonadPlus, Applicative, Alternative, Functor)
-- | @since 4.8.0.0
diff --git a/libraries/base/GHC/Generics.hs b/libraries/base/GHC/Generics.hs
index 2ba16ed5c6..d82679af8c 100644
--- a/libraries/base/GHC/Generics.hs
+++ b/libraries/base/GHC/Generics.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveFunctor #-}
+{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
@@ -85,7 +86,8 @@ module GHC.Generics (
-- 'C1' ('MetaCons \"Node\" 'PrefixI 'False)
-- ('S1' ('MetaSel 'Nothing
-- 'NoSourceUnpackedness
--- 'NoSourceStrictness
+
+ -- 'NoSourceStrictness
-- 'DecidedLazy)
-- ('Rec0' (Tree a))
-- ':*:'
@@ -725,16 +727,19 @@ import Data.Maybe ( Maybe(..), fromMaybe )
import GHC.Integer ( Integer, integerToInt )
import GHC.Prim ( Addr#, Char#, Double#, Float#, Int#, Word# )
import GHC.Ptr ( Ptr )
-import GHC.Types
+import GHC.Types hiding (Any)
-- Needed for instances
import GHC.Arr ( Ix )
import GHC.Base ( Alternative(..), Applicative(..), Functor(..)
- , Monad(..), MonadPlus(..), String )
+ , Monad(..), MonadPlus(..), String
+ , errorWithoutStackTrace )
import GHC.Classes ( Eq(..), Ord(..) )
import GHC.Enum ( Bounded, Enum )
import GHC.Read ( Read(..), lex, readParen )
import GHC.Show ( Show(..), showString )
+import Data.Foldable
+import Data.Monoid
-- Needed for metadata
import Data.Proxy ( Proxy(..) )
@@ -1220,6 +1225,62 @@ deriving instance Generic1 ((,,,,,) a b c d e)
deriving instance Generic1 ((,,,,,,) a b c d e f)
--------------------------------------------------------------------------------
+-- Foldable instances
+--------------------------------------------------------------------------------
+
+-- | @since 4.9.0.0
+instance Foldable U1 where
+ foldMap _ _ = mempty
+ {-# INLINE foldMap #-}
+ fold _ = mempty
+ {-# INLINE fold #-}
+ foldr _ z _ = z
+ {-# INLINE foldr #-}
+ foldl _ z _ = z
+ {-# INLINE foldl #-}
+ foldl1 _ _ = errorWithoutStackTrace "foldl1: U1"
+ foldr1 _ _ = errorWithoutStackTrace "foldr1: U1"
+ length _ = 0
+ null _ = True
+ elem _ _ = False
+ sum _ = 0
+ product _ = 1
+
+deriving instance Foldable V1
+deriving instance Foldable Par1
+deriving instance Foldable f => Foldable (Rec1 f)
+deriving instance Foldable (K1 i c)
+deriving instance Foldable f => Foldable (M1 i c f)
+deriving instance (Foldable f, Foldable g) => Foldable (f :+: g)
+deriving instance (Foldable f, Foldable g) => Foldable (f :*: g)
+deriving instance (Foldable f, Foldable g) => Foldable (f :.: g)
+deriving instance Foldable UAddr
+deriving instance Foldable UChar
+deriving instance Foldable UDouble
+deriving instance Foldable UFloat
+deriving instance Foldable UInt
+deriving instance Foldable UWord
+
+--------------------------------------------------------------------------------
+-- Instances for Data.Monoid
+--------------------------------------------------------------------------------
+deriving instance Generic (Dual a)
+deriving instance Generic1 Dual
+deriving instance Generic (Endo a)
+deriving instance Generic All
+deriving instance Generic Any
+deriving instance Generic (Sum a)
+deriving instance Generic1 Sum
+deriving instance Generic (Product a)
+deriving instance Generic1 Product
+deriving instance Generic (First a)
+deriving instance Generic1 First
+deriving instance Generic (Last a)
+deriving instance Generic1 Last
+deriving instance Generic (Alt f a)
+deriving instance Generic1 (Alt f)
+
+--------------------------------------------------------------------------------
-- Copied from the singletons package
--------------------------------------------------------------------------------