[commit: packages/base] master: Add `{-# MINIMAL #-}` annotations to typeclasses (7ab6249)
git at git.haskell.org
git at git.haskell.org
Wed Sep 18 13:26:35 CEST 2013
Repository : ssh://git@git.haskell.org/base
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/7ab62490dbc1ea7430fe60d5dad9c3b0fa0bedad/base
>---------------------------------------------------------------
commit 7ab62490dbc1ea7430fe60d5dad9c3b0fa0bedad
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Wed Sep 18 10:45:38 2013 +0200
Add `{-# MINIMAL #-}` annotations to typeclasses
This makes use of the new `{-# MINIMAL #-}` facility (see #7633)
for the following typeclasses
- `Bits`
- `Foldable`
- `Fractional`
- `Num`
- `MonadZip`
- `Read`
- `Show`
- `Storable`
- `Traversable`
Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>
>---------------------------------------------------------------
7ab62490dbc1ea7430fe60d5dad9c3b0fa0bedad
Control/Monad/Zip.hs | 1 +
Data/Bits.hs | 5 +++++
Data/Foldable.hs | 1 +
Data/Traversable.hs | 1 +
Foreign/Storable.hs | 4 ++++
GHC/Num.lhs | 1 +
GHC/Read.lhs | 1 +
GHC/Real.lhs | 1 +
GHC/Show.lhs | 1 +
9 files changed, 16 insertions(+)
diff --git a/Control/Monad/Zip.hs b/Control/Monad/Zip.hs
index 824e373..ec13eed 100644
--- a/Control/Monad/Zip.hs
+++ b/Control/Monad/Zip.hs
@@ -47,6 +47,7 @@ class Monad m => MonadZip m where
-- munzip is a member of the class because sometimes
-- you can implement it more efficiently than the
-- above default code. See Trac #4370 comment by giorgidze
+ {-# MINIMAL mzip | mzipWith #-}
instance MonadZip [] where
mzip = zip
diff --git a/Data/Bits.hs b/Data/Bits.hs
index e2eb3fe..76af67b 100644
--- a/Data/Bits.hs
+++ b/Data/Bits.hs
@@ -239,6 +239,11 @@ class Eq a => Bits a where
known as the population count or the Hamming weight. -}
popCount :: a -> Int
+ {-# MINIMAL (.&.), (.|.), xor, complement,
+ (shift | (shiftL, shiftR)),
+ (rotate | (rotateL, rotateR)),
+ bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount #-}
+
class Bits b => FiniteBits b where
finiteBitSize :: b -> Int
diff --git a/Data/Foldable.hs b/Data/Foldable.hs
index de6c056..e61972d 100644
--- a/Data/Foldable.hs
+++ b/Data/Foldable.hs
@@ -151,6 +151,7 @@ class Foldable t where
where
mf Nothing y = Just y
mf (Just x) y = Just (f x y)
+ {-# MINIMAL foldMap | foldr #-}
-- instances for Prelude types
diff --git a/Data/Traversable.hs b/Data/Traversable.hs
index 7872a61..5fa91e8 100644
--- a/Data/Traversable.hs
+++ b/Data/Traversable.hs
@@ -164,6 +164,7 @@ class (Functor t, Foldable t) => Traversable t where
-- and collect the results.
sequence :: Monad m => t (m a) -> m (t a)
sequence = mapM id
+ {-# MINIMAL traverse | sequenceA #-}
-- instances for Prelude types
diff --git a/Foreign/Storable.hs b/Foreign/Storable.hs
index 86e65f8..7441741 100644
--- a/Foreign/Storable.hs
+++ b/Foreign/Storable.hs
@@ -149,6 +149,10 @@ class Storable a where
peek ptr = peekElemOff ptr 0
poke ptr = pokeElemOff ptr 0
+ {-# MINIMAL sizeOf, alignment,
+ (peek | peekElemOff | peekByteOff),
+ (poke | pokeElemOff | pokeByteOff) #-}
+
-- System-dependent, but rather obvious instances
instance Storable Bool where
diff --git a/GHC/Num.lhs b/GHC/Num.lhs
index 689fafc..7cfc377 100644
--- a/GHC/Num.lhs
+++ b/GHC/Num.lhs
@@ -63,6 +63,7 @@ class Num a where
{-# INLINE negate #-}
x - y = x + negate y
negate x = 0 - x
+ {-# MINIMAL (+), (*), abs, signum, fromInteger, (negate | (-)) #-}
-- | the same as @'flip' ('-')@.
--
diff --git a/GHC/Read.lhs b/GHC/Read.lhs
index 05ee4f9..a8494be 100644
--- a/GHC/Read.lhs
+++ b/GHC/Read.lhs
@@ -206,6 +206,7 @@ class Read a where
readList = readPrec_to_S (list readPrec) 0
readPrec = readS_to_Prec readsPrec
readListPrec = readS_to_Prec (\_ -> readList)
+ {-# MINIMAL readsPrec | readPrec #-}
readListDefault :: Read a => ReadS [a]
-- ^ A possible replacement definition for the 'readList' method (GHC only).
diff --git a/GHC/Real.lhs b/GHC/Real.lhs
index 1d53637..5cb79de 100644
--- a/GHC/Real.lhs
+++ b/GHC/Real.lhs
@@ -192,6 +192,7 @@ class (Num a) => Fractional a where
{-# INLINE (/) #-}
recip x = 1 / x
x / y = x * recip y
+ {-# MINIMAL fromRational, (recip | (/)) #-}
-- | Extracting components of fractions.
--
diff --git a/GHC/Show.lhs b/GHC/Show.lhs
index 3f31e38..bce3e73 100644
--- a/GHC/Show.lhs
+++ b/GHC/Show.lhs
@@ -157,6 +157,7 @@ class Show a where
showsPrec _ x s = show x ++ s
show x = shows x ""
showList ls s = showList__ shows ls s
+ {-# MINIMAL showsPrec | show #-}
showList__ :: (a -> ShowS) -> [a] -> ShowS
showList__ _ [] s = "[]" ++ s
More information about the ghc-commits
mailing list