[commit: ghc] ghc-8.0: Added (more) missing instances for Identity and Const (7b8beba)

git at git.haskell.org git at git.haskell.org
Mon Apr 11 01:44:38 UTC 2016


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

On branch  : ghc-8.0
Link       : http://ghc.haskell.org/trac/ghc/changeset/7b8beba76a31b3184413e033c6f86a5dd6c70ac7/ghc

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

commit 7b8beba76a31b3184413e033c6f86a5dd6c70ac7
Author: Shane O'Brien <shane at duairc.com>
Date:   Mon Apr 11 02:53:00 2016 +0200

    Added (more) missing instances for Identity and Const
    
      * `Identity` and `Const` now have `Num`, `Real`, `Integral`,
        `Fractional`, `Floating`, `RealFrac` and `RealFloat` instances
    
      * `Identity` and `Const` now have `Bits` and `FiniteBits` instances
    
      * `Identity` and `Const` now have `IsString` instances
    
    Reviewers: RyanGlScott, austin, hvr, bgamari, ekmett
    
    Reviewed By: ekmett
    
    Subscribers: nomeata, ekmett, RyanGlScott, thomie
    
    Differential Revision: https://phabricator.haskell.org/D2079
    
    GHC Trac Issues: #11790
    
    (cherry picked from commit 8b57cac5974c9fffccbcae3104b5b5d18760749e)


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

7b8beba76a31b3184413e033c6f86a5dd6c70ac7
 libraries/base/Data/Functor/Const.hs    | 11 ++++++++---
 libraries/base/Data/Functor/Identity.hs |  7 +++++--
 libraries/base/Data/String.hs           |  3 +++
 libraries/base/changelog.md             |  6 +++---
 4 files changed, 19 insertions(+), 8 deletions(-)

diff --git a/libraries/base/Data/Functor/Const.hs b/libraries/base/Data/Functor/Const.hs
index 7457951..9f2db7f 100644
--- a/libraries/base/Data/Functor/Const.hs
+++ b/libraries/base/Data/Functor/Const.hs
@@ -1,9 +1,9 @@
-{-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE NoImplicitPrelude #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE Trustworthy #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -21,20 +21,25 @@
 
 module Data.Functor.Const (Const(..)) where
 
+import Data.Bits (Bits, FiniteBits)
 import Data.Foldable (Foldable(foldMap))
 import Foreign.Storable (Storable)
 
 import GHC.Arr (Ix)
 import GHC.Base
 import GHC.Enum (Bounded, Enum)
+import GHC.Float (Floating, RealFloat)
 import GHC.Generics (Generic, Generic1)
+import GHC.Num (Num)
+import GHC.Real (Fractional, Integral, Real, RealFrac)
 import GHC.Read (Read(readsPrec), readParen, lex)
 import GHC.Show (Show(showsPrec), showParen, showString)
 
 -- | The 'Const' functor.
 newtype Const a b = Const { getConst :: a }
-                  deriving ( Generic, Generic1, Bounded, Enum, Eq, Ix, Ord
-                           , Monoid, Storable)
+    deriving ( Bits, Bounded, Enum, Eq, FiniteBits, Floating, Fractional
+             , Generic, Generic1, Integral, Ix, Monoid, Num, Ord, Real
+             , RealFrac, RealFloat , Storable)
 
 -- | This instance would be equivalent to the derived instances of the
 -- 'Const' newtype if the 'runConst' field were removed
diff --git a/libraries/base/Data/Functor/Identity.hs b/libraries/base/Data/Functor/Identity.hs
index df424f2..4e6646a 100644
--- a/libraries/base/Data/Functor/Identity.hs
+++ b/libraries/base/Data/Functor/Identity.hs
@@ -36,11 +36,13 @@ module Data.Functor.Identity (
 
 import Control.Monad.Fix
 import Control.Monad.Zip
+import Data.Bits (Bits, FiniteBits)
 import Data.Coerce
 import Data.Data (Data)
 import Data.Foldable
 import Data.Ix (Ix)
 import Data.Semigroup (Semigroup)
+import Data.String (IsString)
 import Foreign.Storable (Storable)
 import GHC.Generics (Generic, Generic1)
 
@@ -48,8 +50,9 @@ import GHC.Generics (Generic, Generic1)
 --
 -- @since 4.8.0.0
 newtype Identity a = Identity { runIdentity :: a }
-    deriving ( Bounded, Enum, Eq, Ix, Ord, Data, Monoid, Semigroup
-             , Storable, Traversable, Generic, Generic1)
+    deriving ( Bits, Bounded, Data, Enum, Eq, FiniteBits, Floating, Fractional
+             , Generic, Generic1, Integral, IsString, Ix, Monoid, Num, Ord
+             , Real, RealFrac, RealFloat , Semigroup, Storable, Traversable)
 
 -- | This instance would be equivalent to the derived instances of the
 -- 'Identity' newtype if the 'runIdentity' field were removed
diff --git a/libraries/base/Data/String.hs b/libraries/base/Data/String.hs
index 9e1f5f3..f341ff2 100644
--- a/libraries/base/Data/String.hs
+++ b/libraries/base/Data/String.hs
@@ -28,6 +28,7 @@ module Data.String (
  ) where
 
 import GHC.Base
+import Data.Functor.Const (Const (Const))
 import Data.List (lines, words, unlines, unwords)
 
 -- | Class for string-like datastructures; used by the overloaded string
@@ -78,3 +79,5 @@ instance (a ~ Char) => IsString [a] where
          -- See Note [IsString String]
     fromString xs = xs
 
+instance IsString a => IsString (Const a b) where
+    fromString = Const . fromString
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index cb3eced..f935c59 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -131,9 +131,9 @@
 
   * `Identity` now has `Semigroup` and `Monoid` instances
 
-  * `Identity` and `Const` now have `Bounded`, `Enum` and `Ix` instances
-
-  * `Identity` and `Const` now have `Storable` instances
+  * `Identity` and `Const` now have `Bits`, `Bounded`, `Enum`, `FiniteBits`,
+    `Floating`, `Fractional`, `Integral`, `IsString`, `Ix`, `Num`, `Real`,
+    `RealFloat`, `RealFrac` and `Storable` instances. (#11210, #11790)
 
   * `()` now has a `Storable` instance
 



More information about the ghc-commits mailing list