/libraries/base/GHC/Word.hs

https://github.com/tibbe/ghc · Haskell · 798 lines · 512 code · 96 blank · 190 comment · 55 complexity · b7c5236007df5642f73d5b9aa0799ff1 MD5 · raw file

  1. {-# LANGUAGE Trustworthy #-}
  2. {-# LANGUAGE CPP, NoImplicitPrelude, BangPatterns, MagicHash, UnboxedTuples #-}
  3. {-# OPTIONS_HADDOCK hide #-}
  4. -----------------------------------------------------------------------------
  5. -- |
  6. -- Module : GHC.Word
  7. -- Copyright : (c) The University of Glasgow, 1997-2002
  8. -- License : see libraries/base/LICENSE
  9. --
  10. -- Maintainer : cvs-ghc@haskell.org
  11. -- Stability : internal
  12. -- Portability : non-portable (GHC Extensions)
  13. --
  14. -- Sized unsigned integral types: 'Word', 'Word8', 'Word16', 'Word32', and
  15. -- 'Word64'.
  16. --
  17. -----------------------------------------------------------------------------
  18. #include "MachDeps.h"
  19. module GHC.Word (
  20. Word(..), Word8(..), Word16(..), Word32(..), Word64(..),
  21. uncheckedShiftL64#,
  22. uncheckedShiftRL64#,
  23. byteSwap16,
  24. byteSwap32,
  25. byteSwap64
  26. ) where
  27. import Data.Bits
  28. import Data.Maybe
  29. #if WORD_SIZE_IN_BITS < 64
  30. import GHC.IntWord64
  31. #endif
  32. -- import {-# SOURCE #-} GHC.Exception
  33. import GHC.Base
  34. import GHC.Enum
  35. import GHC.Num
  36. import GHC.Real
  37. import GHC.Read
  38. import GHC.Arr
  39. import GHC.Show
  40. import GHC.Float () -- for RealFrac methods
  41. ------------------------------------------------------------------------
  42. -- type Word8
  43. ------------------------------------------------------------------------
  44. -- Word8 is represented in the same way as Word. Operations may assume
  45. -- and must ensure that it holds only values from its logical range.
  46. data {-# CTYPE "HsWord8" #-} Word8 = W8# Word# deriving (Eq, Ord)
  47. -- ^ 8-bit unsigned integer type
  48. instance Show Word8 where
  49. showsPrec p x = showsPrec p (fromIntegral x :: Int)
  50. instance Num Word8 where
  51. (W8# x#) + (W8# y#) = W8# (narrow8Word# (x# `plusWord#` y#))
  52. (W8# x#) - (W8# y#) = W8# (narrow8Word# (x# `minusWord#` y#))
  53. (W8# x#) * (W8# y#) = W8# (narrow8Word# (x# `timesWord#` y#))
  54. negate (W8# x#) = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#))))
  55. abs x = x
  56. signum 0 = 0
  57. signum _ = 1
  58. fromInteger i = W8# (narrow8Word# (integerToWord i))
  59. instance Real Word8 where
  60. toRational x = toInteger x % 1
  61. instance Enum Word8 where
  62. succ x
  63. | x /= maxBound = x + 1
  64. | otherwise = succError "Word8"
  65. pred x
  66. | x /= minBound = x - 1
  67. | otherwise = predError "Word8"
  68. toEnum i@(I# i#)
  69. | i >= 0 && i <= fromIntegral (maxBound::Word8)
  70. = W8# (int2Word# i#)
  71. | otherwise = toEnumError "Word8" i (minBound::Word8, maxBound::Word8)
  72. fromEnum (W8# x#) = I# (word2Int# x#)
  73. enumFrom = boundedEnumFrom
  74. enumFromThen = boundedEnumFromThen
  75. instance Integral Word8 where
  76. quot (W8# x#) y@(W8# y#)
  77. | y /= 0 = W8# (x# `quotWord#` y#)
  78. | otherwise = divZeroError
  79. rem (W8# x#) y@(W8# y#)
  80. | y /= 0 = W8# (x# `remWord#` y#)
  81. | otherwise = divZeroError
  82. div (W8# x#) y@(W8# y#)
  83. | y /= 0 = W8# (x# `quotWord#` y#)
  84. | otherwise = divZeroError
  85. mod (W8# x#) y@(W8# y#)
  86. | y /= 0 = W8# (x# `remWord#` y#)
  87. | otherwise = divZeroError
  88. quotRem (W8# x#) y@(W8# y#)
  89. | y /= 0 = case x# `quotRemWord#` y# of
  90. (# q, r #) ->
  91. (W8# q, W8# r)
  92. | otherwise = divZeroError
  93. divMod (W8# x#) y@(W8# y#)
  94. | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#))
  95. | otherwise = divZeroError
  96. toInteger (W8# x#) = smallInteger (word2Int# x#)
  97. instance Bounded Word8 where
  98. minBound = 0
  99. maxBound = 0xFF
  100. instance Ix Word8 where
  101. range (m,n) = [m..n]
  102. unsafeIndex (m,_) i = fromIntegral (i - m)
  103. inRange (m,n) i = m <= i && i <= n
  104. instance Read Word8 where
  105. readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
  106. instance Bits Word8 where
  107. {-# INLINE shift #-}
  108. {-# INLINE bit #-}
  109. {-# INLINE testBit #-}
  110. (W8# x#) .&. (W8# y#) = W8# (x# `and#` y#)
  111. (W8# x#) .|. (W8# y#) = W8# (x# `or#` y#)
  112. (W8# x#) `xor` (W8# y#) = W8# (x# `xor#` y#)
  113. complement (W8# x#) = W8# (x# `xor#` mb#)
  114. where !(W8# mb#) = maxBound
  115. (W8# x#) `shift` (I# i#)
  116. | isTrue# (i# >=# 0#) = W8# (narrow8Word# (x# `shiftL#` i#))
  117. | otherwise = W8# (x# `shiftRL#` negateInt# i#)
  118. (W8# x#) `shiftL` (I# i#) = W8# (narrow8Word# (x# `shiftL#` i#))
  119. (W8# x#) `unsafeShiftL` (I# i#) =
  120. W8# (narrow8Word# (x# `uncheckedShiftL#` i#))
  121. (W8# x#) `shiftR` (I# i#) = W8# (x# `shiftRL#` i#)
  122. (W8# x#) `unsafeShiftR` (I# i#) = W8# (x# `uncheckedShiftRL#` i#)
  123. (W8# x#) `rotate` (I# i#)
  124. | isTrue# (i'# ==# 0#) = W8# x#
  125. | otherwise = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#`
  126. (x# `uncheckedShiftRL#` (8# -# i'#))))
  127. where
  128. !i'# = word2Int# (int2Word# i# `and#` 7##)
  129. bitSizeMaybe i = Just (finiteBitSize i)
  130. bitSize i = finiteBitSize i
  131. isSigned _ = False
  132. popCount (W8# x#) = I# (word2Int# (popCnt8# x#))
  133. bit = bitDefault
  134. testBit = testBitDefault
  135. instance FiniteBits Word8 where
  136. finiteBitSize _ = 8
  137. {-# RULES
  138. "fromIntegral/Word8->Word8" fromIntegral = id :: Word8 -> Word8
  139. "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer
  140. "fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrow8Word# x#)
  141. "fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# x#)
  142. #-}
  143. {-# RULES
  144. "properFraction/Float->(Word8,Float)"
  145. properFraction = \x ->
  146. case properFraction x of {
  147. (n, y) -> ((fromIntegral :: Int -> Word8) n, y :: Float) }
  148. "truncate/Float->Word8"
  149. truncate = (fromIntegral :: Int -> Word8) . (truncate :: Float -> Int)
  150. "floor/Float->Word8"
  151. floor = (fromIntegral :: Int -> Word8) . (floor :: Float -> Int)
  152. "ceiling/Float->Word8"
  153. ceiling = (fromIntegral :: Int -> Word8) . (ceiling :: Float -> Int)
  154. "round/Float->Word8"
  155. round = (fromIntegral :: Int -> Word8) . (round :: Float -> Int)
  156. #-}
  157. {-# RULES
  158. "properFraction/Double->(Word8,Double)"
  159. properFraction = \x ->
  160. case properFraction x of {
  161. (n, y) -> ((fromIntegral :: Int -> Word8) n, y :: Double) }
  162. "truncate/Double->Word8"
  163. truncate = (fromIntegral :: Int -> Word8) . (truncate :: Double -> Int)
  164. "floor/Double->Word8"
  165. floor = (fromIntegral :: Int -> Word8) . (floor :: Double -> Int)
  166. "ceiling/Double->Word8"
  167. ceiling = (fromIntegral :: Int -> Word8) . (ceiling :: Double -> Int)
  168. "round/Double->Word8"
  169. round = (fromIntegral :: Int -> Word8) . (round :: Double -> Int)
  170. #-}
  171. ------------------------------------------------------------------------
  172. -- type Word16
  173. ------------------------------------------------------------------------
  174. -- Word16 is represented in the same way as Word. Operations may assume
  175. -- and must ensure that it holds only values from its logical range.
  176. data {-# CTYPE "HsWord16" #-} Word16 = W16# Word# deriving (Eq, Ord)
  177. -- ^ 16-bit unsigned integer type
  178. instance Show Word16 where
  179. showsPrec p x = showsPrec p (fromIntegral x :: Int)
  180. instance Num Word16 where
  181. (W16# x#) + (W16# y#) = W16# (narrow16Word# (x# `plusWord#` y#))
  182. (W16# x#) - (W16# y#) = W16# (narrow16Word# (x# `minusWord#` y#))
  183. (W16# x#) * (W16# y#) = W16# (narrow16Word# (x# `timesWord#` y#))
  184. negate (W16# x#) = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#))))
  185. abs x = x
  186. signum 0 = 0
  187. signum _ = 1
  188. fromInteger i = W16# (narrow16Word# (integerToWord i))
  189. instance Real Word16 where
  190. toRational x = toInteger x % 1
  191. instance Enum Word16 where
  192. succ x
  193. | x /= maxBound = x + 1
  194. | otherwise = succError "Word16"
  195. pred x
  196. | x /= minBound = x - 1
  197. | otherwise = predError "Word16"
  198. toEnum i@(I# i#)
  199. | i >= 0 && i <= fromIntegral (maxBound::Word16)
  200. = W16# (int2Word# i#)
  201. | otherwise = toEnumError "Word16" i (minBound::Word16, maxBound::Word16)
  202. fromEnum (W16# x#) = I# (word2Int# x#)
  203. enumFrom = boundedEnumFrom
  204. enumFromThen = boundedEnumFromThen
  205. instance Integral Word16 where
  206. quot (W16# x#) y@(W16# y#)
  207. | y /= 0 = W16# (x# `quotWord#` y#)
  208. | otherwise = divZeroError
  209. rem (W16# x#) y@(W16# y#)
  210. | y /= 0 = W16# (x# `remWord#` y#)
  211. | otherwise = divZeroError
  212. div (W16# x#) y@(W16# y#)
  213. | y /= 0 = W16# (x# `quotWord#` y#)
  214. | otherwise = divZeroError
  215. mod (W16# x#) y@(W16# y#)
  216. | y /= 0 = W16# (x# `remWord#` y#)
  217. | otherwise = divZeroError
  218. quotRem (W16# x#) y@(W16# y#)
  219. | y /= 0 = case x# `quotRemWord#` y# of
  220. (# q, r #) ->
  221. (W16# q, W16# r)
  222. | otherwise = divZeroError
  223. divMod (W16# x#) y@(W16# y#)
  224. | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#))
  225. | otherwise = divZeroError
  226. toInteger (W16# x#) = smallInteger (word2Int# x#)
  227. instance Bounded Word16 where
  228. minBound = 0
  229. maxBound = 0xFFFF
  230. instance Ix Word16 where
  231. range (m,n) = [m..n]
  232. unsafeIndex (m,_) i = fromIntegral (i - m)
  233. inRange (m,n) i = m <= i && i <= n
  234. instance Read Word16 where
  235. readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
  236. instance Bits Word16 where
  237. {-# INLINE shift #-}
  238. {-# INLINE bit #-}
  239. {-# INLINE testBit #-}
  240. (W16# x#) .&. (W16# y#) = W16# (x# `and#` y#)
  241. (W16# x#) .|. (W16# y#) = W16# (x# `or#` y#)
  242. (W16# x#) `xor` (W16# y#) = W16# (x# `xor#` y#)
  243. complement (W16# x#) = W16# (x# `xor#` mb#)
  244. where !(W16# mb#) = maxBound
  245. (W16# x#) `shift` (I# i#)
  246. | isTrue# (i# >=# 0#) = W16# (narrow16Word# (x# `shiftL#` i#))
  247. | otherwise = W16# (x# `shiftRL#` negateInt# i#)
  248. (W16# x#) `shiftL` (I# i#) = W16# (narrow16Word# (x# `shiftL#` i#))
  249. (W16# x#) `unsafeShiftL` (I# i#) =
  250. W16# (narrow16Word# (x# `uncheckedShiftL#` i#))
  251. (W16# x#) `shiftR` (I# i#) = W16# (x# `shiftRL#` i#)
  252. (W16# x#) `unsafeShiftR` (I# i#) = W16# (x# `uncheckedShiftRL#` i#)
  253. (W16# x#) `rotate` (I# i#)
  254. | isTrue# (i'# ==# 0#) = W16# x#
  255. | otherwise = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#`
  256. (x# `uncheckedShiftRL#` (16# -# i'#))))
  257. where
  258. !i'# = word2Int# (int2Word# i# `and#` 15##)
  259. bitSizeMaybe i = Just (finiteBitSize i)
  260. bitSize i = finiteBitSize i
  261. isSigned _ = False
  262. popCount (W16# x#) = I# (word2Int# (popCnt16# x#))
  263. bit = bitDefault
  264. testBit = testBitDefault
  265. instance FiniteBits Word16 where
  266. finiteBitSize _ = 16
  267. -- | Swap bytes in 'Word16'.
  268. --
  269. -- /Since: 4.7.0.0/
  270. byteSwap16 :: Word16 -> Word16
  271. byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#))
  272. {-# RULES
  273. "fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# x#
  274. "fromIntegral/Word16->Word16" fromIntegral = id :: Word16 -> Word16
  275. "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer
  276. "fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#)
  277. "fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# x#)
  278. #-}
  279. {-# RULES
  280. "properFraction/Float->(Word16,Float)"
  281. properFraction = \x ->
  282. case properFraction x of {
  283. (n, y) -> ((fromIntegral :: Int -> Word16) n, y :: Float) }
  284. "truncate/Float->Word16"
  285. truncate = (fromIntegral :: Int -> Word16) . (truncate :: Float -> Int)
  286. "floor/Float->Word16"
  287. floor = (fromIntegral :: Int -> Word16) . (floor :: Float -> Int)
  288. "ceiling/Float->Word16"
  289. ceiling = (fromIntegral :: Int -> Word16) . (ceiling :: Float -> Int)
  290. "round/Float->Word16"
  291. round = (fromIntegral :: Int -> Word16) . (round :: Float -> Int)
  292. #-}
  293. {-# RULES
  294. "properFraction/Double->(Word16,Double)"
  295. properFraction = \x ->
  296. case properFraction x of {
  297. (n, y) -> ((fromIntegral :: Int -> Word16) n, y :: Double) }
  298. "truncate/Double->Word16"
  299. truncate = (fromIntegral :: Int -> Word16) . (truncate :: Double -> Int)
  300. "floor/Double->Word16"
  301. floor = (fromIntegral :: Int -> Word16) . (floor :: Double -> Int)
  302. "ceiling/Double->Word16"
  303. ceiling = (fromIntegral :: Int -> Word16) . (ceiling :: Double -> Int)
  304. "round/Double->Word16"
  305. round = (fromIntegral :: Int -> Word16) . (round :: Double -> Int)
  306. #-}
  307. ------------------------------------------------------------------------
  308. -- type Word32
  309. ------------------------------------------------------------------------
  310. -- Word32 is represented in the same way as Word.
  311. #if WORD_SIZE_IN_BITS > 32
  312. -- Operations may assume and must ensure that it holds only values
  313. -- from its logical range.
  314. -- We can use rewrite rules for the RealFrac methods
  315. {-# RULES
  316. "properFraction/Float->(Word32,Float)"
  317. properFraction = \x ->
  318. case properFraction x of {
  319. (n, y) -> ((fromIntegral :: Int -> Word32) n, y :: Float) }
  320. "truncate/Float->Word32"
  321. truncate = (fromIntegral :: Int -> Word32) . (truncate :: Float -> Int)
  322. "floor/Float->Word32"
  323. floor = (fromIntegral :: Int -> Word32) . (floor :: Float -> Int)
  324. "ceiling/Float->Word32"
  325. ceiling = (fromIntegral :: Int -> Word32) . (ceiling :: Float -> Int)
  326. "round/Float->Word32"
  327. round = (fromIntegral :: Int -> Word32) . (round :: Float -> Int)
  328. #-}
  329. {-# RULES
  330. "properFraction/Double->(Word32,Double)"
  331. properFraction = \x ->
  332. case properFraction x of {
  333. (n, y) -> ((fromIntegral :: Int -> Word32) n, y :: Double) }
  334. "truncate/Double->Word32"
  335. truncate = (fromIntegral :: Int -> Word32) . (truncate :: Double -> Int)
  336. "floor/Double->Word32"
  337. floor = (fromIntegral :: Int -> Word32) . (floor :: Double -> Int)
  338. "ceiling/Double->Word32"
  339. ceiling = (fromIntegral :: Int -> Word32) . (ceiling :: Double -> Int)
  340. "round/Double->Word32"
  341. round = (fromIntegral :: Int -> Word32) . (round :: Double -> Int)
  342. #-}
  343. #endif
  344. data {-# CTYPE "HsWord32" #-} Word32 = W32# Word# deriving (Eq, Ord)
  345. -- ^ 32-bit unsigned integer type
  346. instance Num Word32 where
  347. (W32# x#) + (W32# y#) = W32# (narrow32Word# (x# `plusWord#` y#))
  348. (W32# x#) - (W32# y#) = W32# (narrow32Word# (x# `minusWord#` y#))
  349. (W32# x#) * (W32# y#) = W32# (narrow32Word# (x# `timesWord#` y#))
  350. negate (W32# x#) = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#))))
  351. abs x = x
  352. signum 0 = 0
  353. signum _ = 1
  354. fromInteger i = W32# (narrow32Word# (integerToWord i))
  355. instance Enum Word32 where
  356. succ x
  357. | x /= maxBound = x + 1
  358. | otherwise = succError "Word32"
  359. pred x
  360. | x /= minBound = x - 1
  361. | otherwise = predError "Word32"
  362. toEnum i@(I# i#)
  363. | i >= 0
  364. #if WORD_SIZE_IN_BITS > 32
  365. && i <= fromIntegral (maxBound::Word32)
  366. #endif
  367. = W32# (int2Word# i#)
  368. | otherwise = toEnumError "Word32" i (minBound::Word32, maxBound::Word32)
  369. #if WORD_SIZE_IN_BITS == 32
  370. fromEnum x@(W32# x#)
  371. | x <= fromIntegral (maxBound::Int)
  372. = I# (word2Int# x#)
  373. | otherwise = fromEnumError "Word32" x
  374. enumFrom = integralEnumFrom
  375. enumFromThen = integralEnumFromThen
  376. enumFromTo = integralEnumFromTo
  377. enumFromThenTo = integralEnumFromThenTo
  378. #else
  379. fromEnum (W32# x#) = I# (word2Int# x#)
  380. enumFrom = boundedEnumFrom
  381. enumFromThen = boundedEnumFromThen
  382. #endif
  383. instance Integral Word32 where
  384. quot (W32# x#) y@(W32# y#)
  385. | y /= 0 = W32# (x# `quotWord#` y#)
  386. | otherwise = divZeroError
  387. rem (W32# x#) y@(W32# y#)
  388. | y /= 0 = W32# (x# `remWord#` y#)
  389. | otherwise = divZeroError
  390. div (W32# x#) y@(W32# y#)
  391. | y /= 0 = W32# (x# `quotWord#` y#)
  392. | otherwise = divZeroError
  393. mod (W32# x#) y@(W32# y#)
  394. | y /= 0 = W32# (x# `remWord#` y#)
  395. | otherwise = divZeroError
  396. quotRem (W32# x#) y@(W32# y#)
  397. | y /= 0 = case x# `quotRemWord#` y# of
  398. (# q, r #) ->
  399. (W32# q, W32# r)
  400. | otherwise = divZeroError
  401. divMod (W32# x#) y@(W32# y#)
  402. | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#))
  403. | otherwise = divZeroError
  404. toInteger (W32# x#)
  405. #if WORD_SIZE_IN_BITS == 32
  406. | isTrue# (i# >=# 0#) = smallInteger i#
  407. | otherwise = wordToInteger x#
  408. where
  409. !i# = word2Int# x#
  410. #else
  411. = smallInteger (word2Int# x#)
  412. #endif
  413. instance Bits Word32 where
  414. {-# INLINE shift #-}
  415. {-# INLINE bit #-}
  416. {-# INLINE testBit #-}
  417. (W32# x#) .&. (W32# y#) = W32# (x# `and#` y#)
  418. (W32# x#) .|. (W32# y#) = W32# (x# `or#` y#)
  419. (W32# x#) `xor` (W32# y#) = W32# (x# `xor#` y#)
  420. complement (W32# x#) = W32# (x# `xor#` mb#)
  421. where !(W32# mb#) = maxBound
  422. (W32# x#) `shift` (I# i#)
  423. | isTrue# (i# >=# 0#) = W32# (narrow32Word# (x# `shiftL#` i#))
  424. | otherwise = W32# (x# `shiftRL#` negateInt# i#)
  425. (W32# x#) `shiftL` (I# i#) = W32# (narrow32Word# (x# `shiftL#` i#))
  426. (W32# x#) `unsafeShiftL` (I# i#) =
  427. W32# (narrow32Word# (x# `uncheckedShiftL#` i#))
  428. (W32# x#) `shiftR` (I# i#) = W32# (x# `shiftRL#` i#)
  429. (W32# x#) `unsafeShiftR` (I# i#) = W32# (x# `uncheckedShiftRL#` i#)
  430. (W32# x#) `rotate` (I# i#)
  431. | isTrue# (i'# ==# 0#) = W32# x#
  432. | otherwise = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#`
  433. (x# `uncheckedShiftRL#` (32# -# i'#))))
  434. where
  435. !i'# = word2Int# (int2Word# i# `and#` 31##)
  436. bitSizeMaybe i = Just (finiteBitSize i)
  437. bitSize i = finiteBitSize i
  438. isSigned _ = False
  439. popCount (W32# x#) = I# (word2Int# (popCnt32# x#))
  440. bit = bitDefault
  441. testBit = testBitDefault
  442. instance FiniteBits Word32 where
  443. finiteBitSize _ = 32
  444. {-# RULES
  445. "fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# x#
  446. "fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# x#
  447. "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32
  448. "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer
  449. "fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#)
  450. "fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# x#)
  451. #-}
  452. instance Show Word32 where
  453. #if WORD_SIZE_IN_BITS < 33
  454. showsPrec p x = showsPrec p (toInteger x)
  455. #else
  456. showsPrec p x = showsPrec p (fromIntegral x :: Int)
  457. #endif
  458. instance Real Word32 where
  459. toRational x = toInteger x % 1
  460. instance Bounded Word32 where
  461. minBound = 0
  462. maxBound = 0xFFFFFFFF
  463. instance Ix Word32 where
  464. range (m,n) = [m..n]
  465. unsafeIndex (m,_) i = fromIntegral (i - m)
  466. inRange (m,n) i = m <= i && i <= n
  467. instance Read Word32 where
  468. #if WORD_SIZE_IN_BITS < 33
  469. readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
  470. #else
  471. readsPrec p s = [(fromIntegral (x::Int), r) | (x, r) <- readsPrec p s]
  472. #endif
  473. -- | Reverse order of bytes in 'Word32'.
  474. --
  475. -- /Since: 4.7.0.0/
  476. byteSwap32 :: Word32 -> Word32
  477. byteSwap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#))
  478. ------------------------------------------------------------------------
  479. -- type Word64
  480. ------------------------------------------------------------------------
  481. #if WORD_SIZE_IN_BITS < 64
  482. data {-# CTYPE "HsWord64" #-} Word64 = W64# Word64#
  483. -- ^ 64-bit unsigned integer type
  484. instance Eq Word64 where
  485. (W64# x#) == (W64# y#) = isTrue# (x# `eqWord64#` y#)
  486. (W64# x#) /= (W64# y#) = isTrue# (x# `neWord64#` y#)
  487. instance Ord Word64 where
  488. (W64# x#) < (W64# y#) = isTrue# (x# `ltWord64#` y#)
  489. (W64# x#) <= (W64# y#) = isTrue# (x# `leWord64#` y#)
  490. (W64# x#) > (W64# y#) = isTrue# (x# `gtWord64#` y#)
  491. (W64# x#) >= (W64# y#) = isTrue# (x# `geWord64#` y#)
  492. instance Num Word64 where
  493. (W64# x#) + (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `plusInt64#` word64ToInt64# y#))
  494. (W64# x#) - (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `minusInt64#` word64ToInt64# y#))
  495. (W64# x#) * (W64# y#) = W64# (int64ToWord64# (word64ToInt64# x# `timesInt64#` word64ToInt64# y#))
  496. negate (W64# x#) = W64# (int64ToWord64# (negateInt64# (word64ToInt64# x#)))
  497. abs x = x
  498. signum 0 = 0
  499. signum _ = 1
  500. fromInteger i = W64# (integerToWord64 i)
  501. instance Enum Word64 where
  502. succ x
  503. | x /= maxBound = x + 1
  504. | otherwise = succError "Word64"
  505. pred x
  506. | x /= minBound = x - 1
  507. | otherwise = predError "Word64"
  508. toEnum i@(I# i#)
  509. | i >= 0 = W64# (wordToWord64# (int2Word# i#))
  510. | otherwise = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
  511. fromEnum x@(W64# x#)
  512. | x <= fromIntegral (maxBound::Int)
  513. = I# (word2Int# (word64ToWord# x#))
  514. | otherwise = fromEnumError "Word64" x
  515. enumFrom = integralEnumFrom
  516. enumFromThen = integralEnumFromThen
  517. enumFromTo = integralEnumFromTo
  518. enumFromThenTo = integralEnumFromThenTo
  519. instance Integral Word64 where
  520. quot (W64# x#) y@(W64# y#)
  521. | y /= 0 = W64# (x# `quotWord64#` y#)
  522. | otherwise = divZeroError
  523. rem (W64# x#) y@(W64# y#)
  524. | y /= 0 = W64# (x# `remWord64#` y#)
  525. | otherwise = divZeroError
  526. div (W64# x#) y@(W64# y#)
  527. | y /= 0 = W64# (x# `quotWord64#` y#)
  528. | otherwise = divZeroError
  529. mod (W64# x#) y@(W64# y#)
  530. | y /= 0 = W64# (x# `remWord64#` y#)
  531. | otherwise = divZeroError
  532. quotRem (W64# x#) y@(W64# y#)
  533. | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
  534. | otherwise = divZeroError
  535. divMod (W64# x#) y@(W64# y#)
  536. | y /= 0 = (W64# (x# `quotWord64#` y#), W64# (x# `remWord64#` y#))
  537. | otherwise = divZeroError
  538. toInteger (W64# x#) = word64ToInteger x#
  539. instance Bits Word64 where
  540. {-# INLINE shift #-}
  541. {-# INLINE bit #-}
  542. {-# INLINE testBit #-}
  543. (W64# x#) .&. (W64# y#) = W64# (x# `and64#` y#)
  544. (W64# x#) .|. (W64# y#) = W64# (x# `or64#` y#)
  545. (W64# x#) `xor` (W64# y#) = W64# (x# `xor64#` y#)
  546. complement (W64# x#) = W64# (not64# x#)
  547. (W64# x#) `shift` (I# i#)
  548. | isTrue# (i# >=# 0#) = W64# (x# `shiftL64#` i#)
  549. | otherwise = W64# (x# `shiftRL64#` negateInt# i#)
  550. (W64# x#) `shiftL` (I# i#) = W64# (x# `shiftL64#` i#)
  551. (W64# x#) `unsafeShiftL` (I# i#) = W64# (x# `uncheckedShiftL64#` i#)
  552. (W64# x#) `shiftR` (I# i#) = W64# (x# `shiftRL64#` i#)
  553. (W64# x#) `unsafeShiftR` (I# i#) = W64# (x# `uncheckedShiftRL64#` i#)
  554. (W64# x#) `rotate` (I# i#)
  555. | isTrue# (i'# ==# 0#) = W64# x#
  556. | otherwise = W64# ((x# `uncheckedShiftL64#` i'#) `or64#`
  557. (x# `uncheckedShiftRL64#` (64# -# i'#)))
  558. where
  559. !i'# = word2Int# (int2Word# i# `and#` 63##)
  560. bitSizeMaybe i = Just (finiteBitSize i)
  561. bitSize i = finiteBitSize i
  562. isSigned _ = False
  563. popCount (W64# x#) = I# (word2Int# (popCnt64# x#))
  564. bit = bitDefault
  565. testBit = testBitDefault
  566. -- give the 64-bit shift operations the same treatment as the 32-bit
  567. -- ones (see GHC.Base), namely we wrap them in tests to catch the
  568. -- cases when we're shifting more than 64 bits to avoid unspecified
  569. -- behaviour in the C shift operations.
  570. shiftL64#, shiftRL64# :: Word64# -> Int# -> Word64#
  571. a `shiftL64#` b | isTrue# (b >=# 64#) = wordToWord64# 0##
  572. | otherwise = a `uncheckedShiftL64#` b
  573. a `shiftRL64#` b | isTrue# (b >=# 64#) = wordToWord64# 0##
  574. | otherwise = a `uncheckedShiftRL64#` b
  575. {-# RULES
  576. "fromIntegral/Int->Word64" fromIntegral = \(I# x#) -> W64# (int64ToWord64# (intToInt64# x#))
  577. "fromIntegral/Word->Word64" fromIntegral = \(W# x#) -> W64# (wordToWord64# x#)
  578. "fromIntegral/Word64->Int" fromIntegral = \(W64# x#) -> I# (word2Int# (word64ToWord# x#))
  579. "fromIntegral/Word64->Word" fromIntegral = \(W64# x#) -> W# (word64ToWord# x#)
  580. "fromIntegral/Word64->Word64" fromIntegral = id :: Word64 -> Word64
  581. #-}
  582. #else
  583. -- Word64 is represented in the same way as Word.
  584. -- Operations may assume and must ensure that it holds only values
  585. -- from its logical range.
  586. data {-# CTYPE "HsWord64" #-} Word64 = W64# Word# deriving (Eq, Ord)
  587. -- ^ 64-bit unsigned integer type
  588. instance Num Word64 where
  589. (W64# x#) + (W64# y#) = W64# (x# `plusWord#` y#)
  590. (W64# x#) - (W64# y#) = W64# (x# `minusWord#` y#)
  591. (W64# x#) * (W64# y#) = W64# (x# `timesWord#` y#)
  592. negate (W64# x#) = W64# (int2Word# (negateInt# (word2Int# x#)))
  593. abs x = x
  594. signum 0 = 0
  595. signum _ = 1
  596. fromInteger i = W64# (integerToWord i)
  597. instance Enum Word64 where
  598. succ x
  599. | x /= maxBound = x + 1
  600. | otherwise = succError "Word64"
  601. pred x
  602. | x /= minBound = x - 1
  603. | otherwise = predError "Word64"
  604. toEnum i@(I# i#)
  605. | i >= 0 = W64# (int2Word# i#)
  606. | otherwise = toEnumError "Word64" i (minBound::Word64, maxBound::Word64)
  607. fromEnum x@(W64# x#)
  608. | x <= fromIntegral (maxBound::Int)
  609. = I# (word2Int# x#)
  610. | otherwise = fromEnumError "Word64" x
  611. enumFrom = integralEnumFrom
  612. enumFromThen = integralEnumFromThen
  613. enumFromTo = integralEnumFromTo
  614. enumFromThenTo = integralEnumFromThenTo
  615. instance Integral Word64 where
  616. quot (W64# x#) y@(W64# y#)
  617. | y /= 0 = W64# (x# `quotWord#` y#)
  618. | otherwise = divZeroError
  619. rem (W64# x#) y@(W64# y#)
  620. | y /= 0 = W64# (x# `remWord#` y#)
  621. | otherwise = divZeroError
  622. div (W64# x#) y@(W64# y#)
  623. | y /= 0 = W64# (x# `quotWord#` y#)
  624. | otherwise = divZeroError
  625. mod (W64# x#) y@(W64# y#)
  626. | y /= 0 = W64# (x# `remWord#` y#)
  627. | otherwise = divZeroError
  628. quotRem (W64# x#) y@(W64# y#)
  629. | y /= 0 = case x# `quotRemWord#` y# of
  630. (# q, r #) ->
  631. (W64# q, W64# r)
  632. | otherwise = divZeroError
  633. divMod (W64# x#) y@(W64# y#)
  634. | y /= 0 = (W64# (x# `quotWord#` y#), W64# (x# `remWord#` y#))
  635. | otherwise = divZeroError
  636. toInteger (W64# x#)
  637. | isTrue# (i# >=# 0#) = smallInteger i#
  638. | otherwise = wordToInteger x#
  639. where
  640. !i# = word2Int# x#
  641. instance Bits Word64 where
  642. {-# INLINE shift #-}
  643. {-# INLINE bit #-}
  644. {-# INLINE testBit #-}
  645. (W64# x#) .&. (W64# y#) = W64# (x# `and#` y#)
  646. (W64# x#) .|. (W64# y#) = W64# (x# `or#` y#)
  647. (W64# x#) `xor` (W64# y#) = W64# (x# `xor#` y#)
  648. complement (W64# x#) = W64# (x# `xor#` mb#)
  649. where !(W64# mb#) = maxBound
  650. (W64# x#) `shift` (I# i#)
  651. | isTrue# (i# >=# 0#) = W64# (x# `shiftL#` i#)
  652. | otherwise = W64# (x# `shiftRL#` negateInt# i#)
  653. (W64# x#) `shiftL` (I# i#) = W64# (x# `shiftL#` i#)
  654. (W64# x#) `unsafeShiftL` (I# i#) = W64# (x# `uncheckedShiftL#` i#)
  655. (W64# x#) `shiftR` (I# i#) = W64# (x# `shiftRL#` i#)
  656. (W64# x#) `unsafeShiftR` (I# i#) = W64# (x# `uncheckedShiftRL#` i#)
  657. (W64# x#) `rotate` (I# i#)
  658. | isTrue# (i'# ==# 0#) = W64# x#
  659. | otherwise = W64# ((x# `uncheckedShiftL#` i'#) `or#`
  660. (x# `uncheckedShiftRL#` (64# -# i'#)))
  661. where
  662. !i'# = word2Int# (int2Word# i# `and#` 63##)
  663. bitSizeMaybe i = Just (finiteBitSize i)
  664. bitSize i = finiteBitSize i
  665. isSigned _ = False
  666. popCount (W64# x#) = I# (word2Int# (popCnt64# x#))
  667. bit = bitDefault
  668. testBit = testBitDefault
  669. {-# RULES
  670. "fromIntegral/a->Word64" fromIntegral = \x -> case fromIntegral x of W# x# -> W64# x#
  671. "fromIntegral/Word64->a" fromIntegral = \(W64# x#) -> fromIntegral (W# x#)
  672. #-}
  673. uncheckedShiftL64# :: Word# -> Int# -> Word#
  674. uncheckedShiftL64# = uncheckedShiftL#
  675. uncheckedShiftRL64# :: Word# -> Int# -> Word#
  676. uncheckedShiftRL64# = uncheckedShiftRL#
  677. #endif
  678. instance FiniteBits Word64 where
  679. finiteBitSize _ = 64
  680. instance Show Word64 where
  681. showsPrec p x = showsPrec p (toInteger x)
  682. instance Real Word64 where
  683. toRational x = toInteger x % 1
  684. instance Bounded Word64 where
  685. minBound = 0
  686. maxBound = 0xFFFFFFFFFFFFFFFF
  687. instance Ix Word64 where
  688. range (m,n) = [m..n]
  689. unsafeIndex (m,_) i = fromIntegral (i - m)
  690. inRange (m,n) i = m <= i && i <= n
  691. instance Read Word64 where
  692. readsPrec p s = [(fromInteger x, r) | (x, r) <- readsPrec p s]
  693. -- | Reverse order of bytes in 'Word64'.
  694. --
  695. -- /Since: 4.7.0.0/
  696. #if WORD_SIZE_IN_BITS < 64
  697. byteSwap64 :: Word64 -> Word64
  698. byteSwap64 (W64# w#) = W64# (byteSwap64# w#)
  699. #else
  700. byteSwap64 :: Word64 -> Word64
  701. byteSwap64 (W64# w#) = W64# (byteSwap# w#)
  702. #endif