[project @ 2002-10-01 10:32:11 by ross]
[ghc-base.git] / Data / Bits.hs
1 {-# OPTIONS -fno-implicit-prelude #-}
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module      :  Data.Bits
5 -- Copyright   :  (c) The University of Glasgow 2001
6 -- License     :  BSD-style (see the file libraries/base/LICENSE)
7 -- 
8 -- Maintainer  :  libraries@haskell.org
9 -- Stability   :  experimental
10 -- Portability :  portable
11 --
12 --  This module defines bitwise operations for signed and unsigned
13 --  integers.  Instances of the class 'Bits' for the 'Int' and
14 --  'Integer' types are available from this module, and instances for
15 --  explicitly sized integral types are available from the
16 --  "Int" and "Word" modules.
17 --
18 -----------------------------------------------------------------------------
19
20 module Data.Bits ( 
21   -- * The 'Bits' class
22   Bits(
23     (.&.), (.|.), xor, -- :: a -> a -> a
24     complement,        -- :: a -> a
25     shift,             -- :: a -> Int -> a
26     rotate,            -- :: a -> Int -> a
27     bit,               -- :: Int -> a
28     setBit,            -- :: a -> Int -> a
29     clearBit,          -- :: a -> Int -> a
30     complementBit,     -- :: a -> Int -> a
31     testBit,           -- :: a -> Int -> Bool
32     bitSize,           -- :: a -> Int
33     isSigned           -- :: a -> Bool
34   ),
35
36   -- * Shifts and rotates
37
38   -- $shifts
39   shiftL, shiftR,      -- :: Bits a => a -> Int -> a
40   rotateL, rotateR,    -- :: Bits a => a -> Int -> a
41
42   -- instance Bits Int
43   -- instance Bits Integer
44  ) where
45
46 -- Defines the @Bits@ class containing bit-based operations.
47 -- See library document for details on the semantics of the
48 -- individual operations.
49
50 #ifdef __GLASGOW_HASKELL__
51 #include "MachDeps.h"
52 import GHC.Num
53 import GHC.Real
54 import GHC.Base
55 #endif
56
57 infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
58 infixl 7 .&.
59 infixl 6 `xor`
60 infixl 5 .|.
61
62 {-| 
63 The 'Bits' class defines bitwise operations over integral types.
64
65 * Bits are numbered from 0 with bit 0 being the least
66   significant bit.
67 -}
68 class Num a => Bits a where
69     -- | Bitwise \"and\"
70     (.&.) :: a -> a -> a
71
72     -- | Bitwise \"or\"
73     (.|.) :: a -> a -> a
74
75     -- | Bitwise \"xor\"
76     xor :: a -> a -> a
77
78     {-| Reverse all the bits in the argument -}
79     complement        :: a -> a
80
81     {-| Signed shift the argument left by the specified number of bits.
82         Right shifts are specified by giving a negative value. -}
83     shift             :: a -> Int -> a
84
85     {-| Signed rotate the argument left by the specified number of bits.
86         Right rotates are specified by giving a negative value.
87
88         'rotate' is well defined only if 'bitSize' is also well defined
89         ('bitSize' is undefined for 'Integer', for example).
90     -}
91     rotate            :: a -> Int -> a
92
93     -- | @bit i@ is a value with the @i@th bit set
94     bit               :: Int -> a
95
96     -- | @x \`setBit\` i@ is the same as @x .|. bit i@
97     setBit            :: a -> Int -> a
98
99     -- | @x \`clearBit\` i@ is the same as @x .&. complement (bit i)@
100     clearBit          :: a -> Int -> a
101
102     -- | @x \`complementBit\` i@ is the same as @x \`xor\` bit i@
103     complementBit     :: a -> Int -> a
104
105     -- | Return 'True' if the @n@th bit of the argument is 1
106     testBit           :: a -> Int -> Bool
107
108     {-| Return the number of bits in the type of the argument.  The actual
109         value of the argument is ignored -}
110     bitSize           :: a -> Int
111
112     {-| Return 'True' if the argument is a signed type.  The actual
113         value of the argument is ignored -}
114     isSigned          :: a -> Bool
115
116     bit i               = 1 `shift` i
117     x `setBit` i        = x .|. bit i
118     x `clearBit` i      = x .&. complement (bit i)
119     x `complementBit` i = x `xor` bit i
120     x `testBit` i       = (x .&. bit i) /= 0
121
122 -- $shifts
123 -- These functions might sometimes be more convenient than the unified
124 -- versions 'shift' and 'rotate'.
125
126 shiftL, shiftR   :: Bits a => a -> Int -> a
127 rotateL, rotateR :: Bits a => a -> Int -> a
128 x `shiftL`  i = x `shift`  i
129 x `shiftR`  i = x `shift`  (-i)
130 x `rotateL` i = x `rotate` i
131 x `rotateR` i = x `rotate` (-i)
132
133 #ifdef __GLASGOW_HASKELL__
134 instance Bits Int where
135     (I# x#) .&.   (I# y#)  = I# (word2Int# (int2Word# x# `and#` int2Word# y#))
136     (I# x#) .|.   (I# y#)  = I# (word2Int# (int2Word# x# `or#`  int2Word# y#))
137     (I# x#) `xor` (I# y#)  = I# (word2Int# (int2Word# x# `xor#` int2Word# y#))
138     complement (I# x#)     = I# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
139     (I# x#) `shift` (I# i#)
140         | i# >=# 0#            = I# (x# `iShiftL#` i#)
141         | otherwise            = I# (x# `iShiftRA#` negateInt# i#)
142     (I# x#) `rotate` (I# i#) =
143         I# (word2Int# ((x'# `shiftL#` i'#) `or#`
144                        (x'# `shiftRL#` (wsib -# i'#))))
145         where
146         x'# = int2Word# x#
147         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
148         wsib = WORD_SIZE_IN_BITS#   {- work around preprocessor problem (??) -}
149     bitSize  _                 = WORD_SIZE_IN_BITS
150     isSigned _                 = True
151
152 instance Bits Integer where
153    (S# x) .&. (S# y) = S# (word2Int# (int2Word# x `and#` int2Word# y))
154    x@(S# _) .&. y = toBig x .&. y
155    x .&. y@(S# _) = x .&. toBig y
156    (J# s1 d1) .&. (J# s2 d2) = 
157         case andInteger# s1 d1 s2 d2 of
158           (# s, d #) -> J# s d
159    
160    (S# x) .|. (S# y) = S# (word2Int# (int2Word# x `or#` int2Word# y))
161    x@(S# _) .|. y = toBig x .|. y
162    x .|. y@(S# _) = x .|. toBig y
163    (J# s1 d1) .|. (J# s2 d2) = 
164         case orInteger# s1 d1 s2 d2 of
165           (# s, d #) -> J# s d
166    
167    (S# x) `xor` (S# y) = S# (word2Int# (int2Word# x `xor#` int2Word# y))
168    x@(S# _) `xor` y = toBig x `xor` y
169    x `xor` y@(S# _) = x `xor` toBig y
170    (J# s1 d1) `xor` (J# s2 d2) =
171         case xorInteger# s1 d1 s2 d2 of
172           (# s, d #) -> J# s d
173    
174    complement (S# x) = S# (word2Int# (int2Word# x `xor#` int2Word# (0# -# 1#)))
175    complement (J# s d) = case complementInteger# s d of (# s, d #) -> J# s d
176
177    shift x i | i >= 0    = x * 2^i
178              | otherwise = x `div` 2^(-i)
179
180    rotate x i = shift x i   -- since an Integer never wraps around
181
182    bitSize _  = error "Bits.bitSize(Integer)"
183    isSigned _ = True
184 #endif