[commit: ghc] master: GHC.Word: Move Read instances to GHC.Read (bc21ea0)
git at git.haskell.org
git at git.haskell.org
Fri Mar 17 08:29:52 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/bc21ea0ac849916bd444a1d935d44a110b815e00/ghc
>---------------------------------------------------------------
commit bc21ea0ac849916bd444a1d935d44a110b815e00
Author: Erik de Castro Lopo <erik.decastrolopo at ambiata.com>
Date: Fri Mar 17 17:47:33 2017 +1100
GHC.Word: Move Read instances to GHC.Read
Test Plan: Validate
Reviewers: hvr, austin, bgamari
Reviewed By: hvr
Subscribers: rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3353
>---------------------------------------------------------------
bc21ea0ac849916bd444a1d935d44a110b815e00
libraries/base/Data/Word.hs | 1 +
libraries/base/GHC/Read.hs | 25 ++++++++++++++++++++++++-
libraries/base/GHC/Word.hs | 21 ---------------------
3 files changed, 25 insertions(+), 22 deletions(-)
diff --git a/libraries/base/Data/Word.hs b/libraries/base/Data/Word.hs
index f20844f..b341f9c 100644
--- a/libraries/base/Data/Word.hs
+++ b/libraries/base/Data/Word.hs
@@ -31,6 +31,7 @@ module Data.Word
) where
import GHC.Word
+import GHC.Read () -- Need the `Read` instance for types defined in `GHC.Word`.
{- $notes
diff --git a/libraries/base/GHC/Read.hs b/libraries/base/GHC/Read.hs
index ad505bb..49c0606 100644
--- a/libraries/base/GHC/Read.hs
+++ b/libraries/base/GHC/Read.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, StandaloneDeriving, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, NoImplicitPrelude, StandaloneDeriving, ScopedTypeVariables #-}
{-# OPTIONS_HADDOCK hide #-}
-----------------------------------------------------------------------------
@@ -42,6 +42,8 @@ module GHC.Read
)
where
+#include "MachDeps.h"
+
import qualified Text.ParserCombinators.ReadP as P
import Text.ParserCombinators.ReadP
@@ -66,6 +68,7 @@ import GHC.Float
import GHC.Show
import GHC.Base
import GHC.Arr
+import GHC.Word
-- | @'readParen' 'True' p@ parses what @p@ parses, but surrounded with
@@ -521,6 +524,26 @@ instance Read Word where
readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
-- | @since 2.01
+instance Read Word8 where
+ readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
+
+-- | @since 2.01
+instance Read Word16 where
+ readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
+
+-- | @since 2.01
+instance Read Word32 where
+#if WORD_SIZE_IN_BITS < 33
+ readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
+#else
+ readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
+#endif
+
+-- | @since 2.01
+instance Read Word64 where
+ readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
+
+-- | @since 2.01
instance Read Integer where
readPrec = readNumber convertInt
readListPrec = readListPrecDefault
diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs
index d4a5536..1df9d14 100644
--- a/libraries/base/GHC/Word.hs
+++ b/libraries/base/GHC/Word.hs
@@ -51,7 +51,6 @@ import GHC.Base
import GHC.Enum
import GHC.Num
import GHC.Real
-import GHC.Read
import GHC.Arr
import GHC.Show
@@ -165,10 +164,6 @@ instance Ix Word8 where
inRange (m,n) i = m <= i && i <= n
-- | @since 2.01
-instance Read Word8 where
- readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
-
--- | @since 2.01
instance Bits Word8 where
{-# INLINE shift #-}
{-# INLINE bit #-}
@@ -353,10 +348,6 @@ instance Ix Word16 where
inRange (m,n) i = m <= i && i <= n
-- | @since 2.01
-instance Read Word16 where
- readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
-
--- | @since 2.01
instance Bits Word16 where
{-# INLINE shift #-}
{-# INLINE bit #-}
@@ -657,14 +648,6 @@ instance Ix Word32 where
unsafeIndex (m,_) i = fromIntegral (i - m)
inRange (m,n) i = m <= i && i <= n
--- | @since 2.01
-instance Read Word32 where
-#if WORD_SIZE_IN_BITS < 33
- readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
-#else
- readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
-#endif
-
-- | Reverse order of bytes in 'Word32'.
--
-- @since 4.7.0.0
@@ -979,10 +962,6 @@ instance Ix Word64 where
unsafeIndex (m,_) i = fromIntegral (i - m)
inRange (m,n) i = m <= i && i <= n
--- | @since 2.01
-instance Read Word64 where
- readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
-
-- | Reverse order of bytes in 'Word64'.
--
-- @since 4.7.0.0
More information about the ghc-commits
mailing list