diff options
author | Ian Lynagh <igloo@earth.li> | 2012-05-21 23:20:41 +0100 |
---|---|---|
committer | Ian Lynagh <igloo@earth.li> | 2012-05-21 23:20:41 +0100 |
commit | fda6ab95c82cd0f564d52bc06464fcff9670430c (patch) | |
tree | 38769d2793fc6c394bce367654b5c5858894a9f2 /libraries | |
parent | c06e2a461ad6b095a387e9fe773e61ff8977727a (diff) | |
download | haskell-fda6ab95c82cd0f564d52bc06464fcff9670430c.tar.gz |
Move the Word type from base to ghc-prim
Diffstat (limited to 'libraries')
-rw-r--r-- | libraries/base/Data/Bits.hs | 32 | ||||
-rw-r--r-- | libraries/base/Foreign/Ptr.hs | 3 | ||||
-rw-r--r-- | libraries/base/GHC/Arr.lhs | 6 | ||||
-rw-r--r-- | libraries/base/GHC/Enum.lhs | 20 | ||||
-rw-r--r-- | libraries/base/GHC/Event/IntMap.hs | 4 | ||||
-rw-r--r-- | libraries/base/GHC/Num.lhs | 18 | ||||
-rw-r--r-- | libraries/base/GHC/Read.lhs | 3 | ||||
-rw-r--r-- | libraries/base/GHC/Real.lhs | 67 | ||||
-rw-r--r-- | libraries/base/GHC/Show.lhs | 10 | ||||
-rw-r--r-- | libraries/base/GHC/Word.hs | 134 |
10 files changed, 156 insertions, 141 deletions
diff --git a/libraries/base/Data/Bits.hs b/libraries/base/Data/Bits.hs index 9d8b60ab96..14a6357642 100644 --- a/libraries/base/Data/Bits.hs +++ b/libraries/base/Data/Bits.hs @@ -54,6 +54,7 @@ module Data.Bits ( #endif #ifdef __GLASGOW_HASKELL__ +import GHC.Enum import GHC.Num import GHC.Base #endif @@ -346,6 +347,37 @@ foreign import ccall nhc_primIntRsh :: Int -> Int -> Int foreign import ccall nhc_primIntCompl :: Int -> Int #endif /* __NHC__ */ +#if defined(__GLASGOW_HASKELL__) +instance Bits Word where + {-# INLINE shift #-} + {-# INLINE bit #-} + {-# INLINE testBit #-} + + (W# x#) .&. (W# y#) = W# (x# `and#` y#) + (W# x#) .|. (W# y#) = W# (x# `or#` y#) + (W# x#) `xor` (W# y#) = W# (x# `xor#` y#) + complement (W# x#) = W# (x# `xor#` mb#) + where !(W# mb#) = maxBound + (W# x#) `shift` (I# i#) + | i# >=# 0# = W# (x# `shiftL#` i#) + | otherwise = W# (x# `shiftRL#` negateInt# i#) + (W# x#) `shiftL` (I# i#) = W# (x# `shiftL#` i#) + (W# x#) `unsafeShiftL` (I# i#) = W# (x# `uncheckedShiftL#` i#) + (W# x#) `shiftR` (I# i#) = W# (x# `shiftRL#` i#) + (W# x#) `unsafeShiftR` (I# i#) = W# (x# `uncheckedShiftRL#` i#) + (W# x#) `rotate` (I# i#) + | i'# ==# 0# = W# x# + | otherwise = W# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (wsib -# i'#))) + where + !i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#)) + !wsib = WORD_SIZE_IN_BITS# {- work around preprocessor problem (??) -} + bitSize _ = WORD_SIZE_IN_BITS + isSigned _ = False + popCount (W# x#) = I# (word2Int# (popCnt# x#)) + bit = bitDefault + testBit = testBitDefault +#endif + instance Bits Integer where #if defined(__GLASGOW_HASKELL__) (.&.) = andInteger diff --git a/libraries/base/Foreign/Ptr.hs b/libraries/base/Foreign/Ptr.hs index 56a369241a..3bab833593 100644 --- a/libraries/base/Foreign/Ptr.hs +++ b/libraries/base/Foreign/Ptr.hs @@ -66,9 +66,6 @@ import GHC.Read import GHC.Real import GHC.Show import GHC.Enum -import GHC.Word ( Word(..) ) - -import Data.Word #else import Control.Monad ( liftM ) import Foreign.C.Types diff --git a/libraries/base/GHC/Arr.lhs b/libraries/base/GHC/Arr.lhs index 0b3d91833a..4c5827addd 100644 --- a/libraries/base/GHC/Arr.lhs +++ b/libraries/base/GHC/Arr.lhs @@ -47,6 +47,7 @@ import GHC.Num import GHC.ST import GHC.Base import GHC.List +import GHC.Real import GHC.Show infixl 9 !, // @@ -228,6 +229,11 @@ instance Ix Int where {-# INLINE inRange #-} inRange (I# m,I# n) (I# i) = m <=# i && i <=# n +instance Ix Word where + range (m,n) = [m..n] + unsafeIndex (m,_) i = fromIntegral (i - m) + inRange (m,n) i = m <= i && i <= n + ---------------------------------------------------------------------- instance Ix Integer where {-# INLINE range #-} diff --git a/libraries/base/GHC/Enum.lhs b/libraries/base/GHC/Enum.lhs index 2240117c3b..b186b44cfd 100644 --- a/libraries/base/GHC/Enum.lhs +++ b/libraries/base/GHC/Enum.lhs @@ -623,6 +623,26 @@ efdtIntDnFB c n x1 x2 y -- Be careful about underflow! %********************************************************* %* * +\subsection{Type @Word@} +%* * +%********************************************************* + +\begin{code} +instance Bounded Word where + minBound = 0 + + -- use unboxed literals for maxBound, because GHC doesn't optimise + -- (fromInteger 0xffffffff :: Word). +#if WORD_SIZE_IN_BITS == 32 + maxBound = W# (int2Word# 0xFFFFFFFF#) +#else + maxBound = W# (int2Word# 0xFFFFFFFFFFFFFFFF#) +#endif +\end{code} + + +%********************************************************* +%* * \subsection{The @Integer@ instance for @Enum@} %* * %********************************************************* diff --git a/libraries/base/GHC/Event/IntMap.hs b/libraries/base/GHC/Event/IntMap.hs index eee0cc5fa9..6c397e5df0 100644 --- a/libraries/base/GHC/Event/IntMap.hs +++ b/libraries/base/GHC/Event/IntMap.hs @@ -78,9 +78,7 @@ import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (Show(showsPrec), showParen, shows, showString) -#if __GLASGOW_HASKELL__ -import GHC.Word (Word(..)) -#else +#if !defined(__GLASGOW_HASKELL__) import Data.Word #endif diff --git a/libraries/base/GHC/Num.lhs b/libraries/base/GHC/Num.lhs index fba9c48a55..689fafc9a5 100644 --- a/libraries/base/GHC/Num.lhs +++ b/libraries/base/GHC/Num.lhs @@ -99,6 +99,24 @@ instance Num Int where %********************************************************* %* * +\subsection{Instances for @Word@} +%* * +%********************************************************* + +\begin{code} +instance Num Word where + (W# x#) + (W# y#) = W# (x# `plusWord#` y#) + (W# x#) - (W# y#) = W# (x# `minusWord#` y#) + (W# x#) * (W# y#) = W# (x# `timesWord#` y#) + negate (W# x#) = W# (int2Word# (negateInt# (word2Int# x#))) + abs x = x + signum 0 = 0 + signum _ = 1 + fromInteger i = W# (integerToWord i) +\end{code} + +%********************************************************* +%* * \subsection{The @Integer@ instances for @Num@} %* * %********************************************************* diff --git a/libraries/base/GHC/Read.lhs b/libraries/base/GHC/Read.lhs index 1b3be3dd18..26463cc634 100644 --- a/libraries/base/GHC/Read.lhs +++ b/libraries/base/GHC/Read.lhs @@ -488,6 +488,9 @@ instance Read Int where readListPrec = readListPrecDefault readList = readListDefault +instance Read Word where + readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s] + instance Read Integer where readPrec = readNumber convertInt readListPrec = readListPrecDefault diff --git a/libraries/base/GHC/Real.lhs b/libraries/base/GHC/Real.lhs index a0dfbc76d3..2e2ff09c02 100644 --- a/libraries/base/GHC/Real.lhs +++ b/libraries/base/GHC/Real.lhs @@ -1,6 +1,7 @@ \begin{code} {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples #-} +{-# LANGUAGE CPP, NoImplicitPrelude, MagicHash, UnboxedTuples, BangPatterns #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_HADDOCK hide #-} ----------------------------------------------------------------------------- -- | @@ -292,6 +293,64 @@ instance Integral Int where %********************************************************* %* * +\subsection{Instances for @Word@} +%* * +%********************************************************* + +\begin{code} +instance Real Word where + toRational x = toInteger x % 1 + +instance Integral Word where + quot (W# x#) y@(W# y#) + | y /= 0 = W# (x# `quotWord#` y#) + | otherwise = divZeroError + rem (W# x#) y@(W# y#) + | y /= 0 = W# (x# `remWord#` y#) + | otherwise = divZeroError + div (W# x#) y@(W# y#) + | y /= 0 = W# (x# `quotWord#` y#) + | otherwise = divZeroError + mod (W# x#) y@(W# y#) + | y /= 0 = W# (x# `remWord#` y#) + | otherwise = divZeroError + quotRem (W# x#) y@(W# y#) + | y /= 0 = case x# `quotRemWord#` y# of + (# q, r #) -> + (W# q, W# r) + | otherwise = divZeroError + divMod (W# x#) y@(W# y#) + | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#)) + | otherwise = divZeroError + toInteger (W# x#) + | i# >=# 0# = smallInteger i# + | otherwise = wordToInteger x# + where + !i# = word2Int# x# + +instance Enum Word where + succ x + | x /= maxBound = x + 1 + | otherwise = succError "Word" + pred x + | x /= minBound = x - 1 + | otherwise = predError "Word" + toEnum i@(I# i#) + | i >= 0 = W# (int2Word# i#) + | otherwise = toEnumError "Word" i (minBound::Word, maxBound::Word) + fromEnum x@(W# x#) + | x <= fromIntegral (maxBound::Int) + = I# (word2Int# x#) + | otherwise = fromEnumError "Word" x + enumFrom = integralEnumFrom + enumFromThen = integralEnumFromThen + enumFromTo = integralEnumFromTo + enumFromThenTo = integralEnumFromThenTo +\end{code} + + +%********************************************************* +%* * \subsection{Instances for @Integer@} %* * %********************************************************* @@ -403,6 +462,12 @@ fromIntegral = fromInteger . toInteger "fromIntegral/Int->Int" fromIntegral = id :: Int -> Int #-} +{-# RULES +"fromIntegral/Int->Word" fromIntegral = \(I# x#) -> W# (int2Word# x#) +"fromIntegral/Word->Int" fromIntegral = \(W# x#) -> I# (word2Int# x#) +"fromIntegral/Word->Word" fromIntegral = id :: Word -> Word + #-} + -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b realToFrac = fromRational . toRational diff --git a/libraries/base/GHC/Show.lhs b/libraries/base/GHC/Show.lhs index 906bb7bc16..458377dda5 100644 --- a/libraries/base/GHC/Show.lhs +++ b/libraries/base/GHC/Show.lhs @@ -206,6 +206,16 @@ instance Show Char where instance Show Int where showsPrec = showSignedInt +instance Show Word where + showsPrec _ (W# w) = showWord w + +showWord :: Word# -> ShowS +showWord w# cs + | w# `ltWord#` 10## = C# (chr# (ord# '0'# +# word2Int# w#)) : cs + | otherwise = case chr# (ord# '0'# +# word2Int# (w# `remWord#` 10##)) of + c# -> + showWord (w# `quotWord#` 10##) (C# c# : cs) + instance Show a => Show (Maybe a) where showsPrec _p Nothing s = showString "Nothing" s showsPrec p (Just x) s diff --git a/libraries/base/GHC/Word.hs b/libraries/base/GHC/Word.hs index 0dcb0e32f8..781520fea0 100644 --- a/libraries/base/GHC/Word.hs +++ b/libraries/base/GHC/Word.hs @@ -43,140 +43,6 @@ import GHC.Err import GHC.Float () -- for RealFrac methods ------------------------------------------------------------------------ --- type Word ------------------------------------------------------------------------- - --- |A 'Word' is an unsigned integral type, with the same size as 'Int'. -data {-# CTYPE "HsWord" #-} Word = W# Word# deriving (Eq, Ord) - -instance Show Word where - showsPrec _ (W# w) = showWord w - -showWord :: Word# -> ShowS -showWord w# cs - | w# `ltWord#` 10## = C# (chr# (ord# '0'# +# word2Int# w#)) : cs - | otherwise = case chr# (ord# '0'# +# word2Int# (w# `remWord#` 10##)) of - c# -> - showWord (w# `quotWord#` 10##) (C# c# : cs) - -instance Num Word where - (W# x#) + (W# y#) = W# (x# `plusWord#` y#) - (W# x#) - (W# y#) = W# (x# `minusWord#` y#) - (W# x#) * (W# y#) = W# (x# `timesWord#` y#) - negate (W# x#) = W# (int2Word# (negateInt# (word2Int# x#))) - abs x = x - signum 0 = 0 - signum _ = 1 - fromInteger i = W# (integerToWord i) - -instance Real Word where - toRational x = toInteger x % 1 - -instance Enum Word where - succ x - | x /= maxBound = x + 1 - | otherwise = succError "Word" - pred x - | x /= minBound = x - 1 - | otherwise = predError "Word" - toEnum i@(I# i#) - | i >= 0 = W# (int2Word# i#) - | otherwise = toEnumError "Word" i (minBound::Word, maxBound::Word) - fromEnum x@(W# x#) - | x <= fromIntegral (maxBound::Int) - = I# (word2Int# x#) - | otherwise = fromEnumError "Word" x - enumFrom = integralEnumFrom - enumFromThen = integralEnumFromThen - enumFromTo = integralEnumFromTo - enumFromThenTo = integralEnumFromThenTo - -instance Integral Word where - quot (W# x#) y@(W# y#) - | y /= 0 = W# (x# `quotWord#` y#) - | otherwise = divZeroError - rem (W# x#) y@(W# y#) - | y /= 0 = W# (x# `remWord#` y#) - | otherwise = divZeroError - div (W# x#) y@(W# y#) - | y /= 0 = W# (x# `quotWord#` y#) - | otherwise = divZeroError - mod (W# x#) y@(W# y#) - | y /= 0 = W# (x# `remWord#` y#) - | otherwise = divZeroError - quotRem (W# x#) y@(W# y#) - | y /= 0 = case x# `quotRemWord#` y# of - (# q, r #) -> - (W# q, W# r) - | otherwise = divZeroError - divMod (W# x#) y@(W# y#) - | y /= 0 = (W# (x# `quotWord#` y#), W# (x# `remWord#` y#)) - | otherwise = divZeroError - toInteger (W# x#) - | i# >=# 0# = smallInteger i# - | otherwise = wordToInteger x# - where - !i# = word2Int# x# - -instance Bounded Word where - minBound = 0 - - -- use unboxed literals for maxBound, because GHC doesn't optimise - -- (fromInteger 0xffffffff :: Word). -#if WORD_SIZE_IN_BITS == 32 - maxBound = W# 0xFFFFFFFF## -#else - maxBound = W# 0xFFFFFFFFFFFFFFFF## -#endif - -instance Ix Word where - range (m,n) = [m..n] - unsafeIndex (m,_) i = fromIntegral (i - m) - inRange (m,n) i = m <= i && i <= n - -instance Read Word where - readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s] - -instance Bits Word where - {-# INLINE shift #-} - {-# INLINE bit #-} - {-# INLINE testBit #-} - - (W# x#) .&. (W# y#) = W# (x# `and#` y#) - (W# x#) .|. (W# y#) = W# (x# `or#` y#) - (W# x#) `xor` (W# y#) = W# (x# `xor#` y#) - complement (W# x#) = W# (x# `xor#` mb#) - where !(W# mb#) = maxBound - (W# x#) `shift` (I# i#) - | i# >=# 0# = W# (x# `shiftL#` i#) - | otherwise = W# (x# `shiftRL#` negateInt# i#) - (W# x#) `shiftL` (I# i#) = W# (x# `shiftL#` i#) - (W# x#) `unsafeShiftL` (I# i#) = W# (x# `uncheckedShiftL#` i#) - (W# x#) `shiftR` (I# i#) = W# (x# `shiftRL#` i#) - (W# x#) `unsafeShiftR` (I# i#) = W# (x# `uncheckedShiftRL#` i#) - (W# x#) `rotate` (I# i#) - | i'# ==# 0# = W# x# - | otherwise = W# ((x# `uncheckedShiftL#` i'#) `or#` (x# `uncheckedShiftRL#` (wsib -# i'#))) - where - !i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#)) - !wsib = WORD_SIZE_IN_BITS# {- work around preprocessor problem (??) -} - bitSize _ = WORD_SIZE_IN_BITS - isSigned _ = False - popCount (W# x#) = I# (word2Int# (popCnt# x#)) - bit = bitDefault - testBit = testBitDefault - -{-# RULES -"fromIntegral/Int->Word" fromIntegral = \(I# x#) -> W# (int2Word# x#) -"fromIntegral/Word->Int" fromIntegral = \(W# x#) -> I# (word2Int# x#) -"fromIntegral/Word->Word" fromIntegral = id :: Word -> Word - #-} - --- No RULES for RealFrac unfortunately. --- Going through Int isn't possible because Word's range is not --- included in Int's, going through Integer may or may not be slower. - ------------------------------------------------------------------------- -- type Word8 ------------------------------------------------------------------------ |