summaryrefslogtreecommitdiff
path: root/libraries/base/GHC/Word.hs
diff options
context:
space:
mode:
authorIan Lynagh <igloo@earth.li>2012-05-21 23:20:41 +0100
committerIan Lynagh <igloo@earth.li>2012-05-21 23:20:41 +0100
commitfda6ab95c82cd0f564d52bc06464fcff9670430c (patch)
tree38769d2793fc6c394bce367654b5c5858894a9f2 /libraries/base/GHC/Word.hs
parentc06e2a461ad6b095a387e9fe773e61ff8977727a (diff)
downloadhaskell-fda6ab95c82cd0f564d52bc06464fcff9670430c.tar.gz
Move the Word type from base to ghc-prim
Diffstat (limited to 'libraries/base/GHC/Word.hs')
-rw-r--r--libraries/base/GHC/Word.hs134
1 files changed, 0 insertions, 134 deletions
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
------------------------------------------------------------------------