[project @ 2002-05-10 13:42:07 by simonmar]
[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 --ADR: The fixity for .|. conflicts with that for .|. in Fran.
58 --     Removing all fixities is a fairly safe fix; fixing the "one fixity
59 --     per symbol per program" limitation in Hugs would take a lot longer.
60 #ifndef __HUGS__
61 infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
62 infixl 7 .&.
63 infixl 6 `xor`
64 infixl 5 .|.
65 #endif
66
67 {-| 
68 The 'Bits' class defines bitwise operations over integral types.
69
70 * Bits are numbered from 0 with bit 0 being the least
71   significant bit.
72 -}
73 class Num a => Bits a where
74     -- | Bitwise \"and\"
75     (.&.) :: a -> a -> a
76
77     -- | Bitwise \"or\"
78     (.|.) :: a -> a -> a
79
80     -- | Bitwise \"xor\"
81     xor :: a -> a -> a
82
83     {-| Reverse all the bits in the argument -}
84     complement        :: a -> a
85
86     {-| Signed shift the argument left by the specified number of bits.
87         Right shifts are specified by giving a negative value. -}
88     shift             :: a -> Int -> a
89
90     {-| Signed rotate the argument left by the specified number of bits.
91         Right rotates are specified by giving a negative value.
92
93         'rotate' is well defined only if 'bitSize' is also well defined
94         ('bitSize' is undefined for 'Integer', for example).
95     -}
96     rotate            :: a -> Int -> a
97
98     -- | @bit i@ is a value with the @i@th bit set
99     bit               :: Int -> a
100
101     -- | @x \`setBit\` i@ is the same as @x .|. bit i@
102     setBit            :: a -> Int -> a
103
104     -- | @x \`clearBit\` i@ is the same as @x .&. complement (bit i)@
105     clearBit          :: a -> Int -> a
106
107     -- | @x \`complementBit\` i@ is the same as @x \`xor\` bit i@
108     complementBit     :: a -> Int -> a
109
110     -- | Return 'True' if the @n@th bit of the argument is 1
111     testBit           :: a -> Int -> Bool
112
113     {-| Return the number of bits in the type of the argument.  The actual
114         value of the argument is ignored -}
115     bitSize           :: a -> Int
116
117     {-| Return 'True' if the argument is a signed type.  The actual
118         value of the argument is ignored -}
119     isSigned          :: a -> Bool
120
121     bit i               = 1 `shift` i
122     x `setBit` i        = x .|. bit i
123     x `clearBit` i      = x .&. complement (bit i)
124     x `complementBit` i = x `xor` bit i
125     x `testBit` i       = (x .&. bit i) /= 0
126
127 -- $shifts
128 -- These functions might sometimes be more convenient than the unified
129 -- versions 'shift' and 'rotate'.
130
131 shiftL, shiftR   :: Bits a => a -> Int -> a
132 rotateL, rotateR :: Bits a => a -> Int -> a
133 x `shiftL`  i = x `shift`  i
134 x `shiftR`  i = x `shift`  (-i)
135 x `rotateL` i = x `rotate` i
136 x `rotateR` i = x `rotate` (-i)
137
138 #ifdef __GLASGOW_HASKELL__
139 instance Bits Int where
140     (I# x#) .&.   (I# y#)  = I# (word2Int# (int2Word# x# `and#` int2Word# y#))
141     (I# x#) .|.   (I# y#)  = I# (word2Int# (int2Word# x# `or#`  int2Word# y#))
142     (I# x#) `xor` (I# y#)  = I# (word2Int# (int2Word# x# `xor#` int2Word# y#))
143     complement (I# x#)     = I# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
144     (I# x#) `shift` (I# i#)
145         | i# >=# 0#            = I# (x# `iShiftL#` i#)
146         | otherwise            = I# (x# `iShiftRA#` negateInt# i#)
147     (I# x#) `rotate` (I# i#) =
148         I# (word2Int# ((x'# `shiftL#` i'#) `or#`
149                        (x'# `shiftRL#` (wsib -# i'#))))
150         where
151         x'# = int2Word# x#
152         i'# = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
153         wsib = WORD_SIZE_IN_BITS#   {- work around preprocessor problem (??) -}
154     bitSize  _                 = WORD_SIZE_IN_BITS
155     isSigned _                 = True
156
157 instance Bits Integer where
158    (S# x) .&. (S# y) = S# (word2Int# (int2Word# x `and#` int2Word# y))
159    x@(S# _) .&. y = toBig x .&. y
160    x .&. y@(S# _) = x .&. toBig y
161    (J# s1 d1) .&. (J# s2 d2) = 
162         case andInteger# s1 d1 s2 d2 of
163           (# s, d #) -> J# s d
164    
165    (S# x) .|. (S# y) = S# (word2Int# (int2Word# x `or#` int2Word# y))
166    x@(S# _) .|. y = toBig x .|. y
167    x .|. y@(S# _) = x .|. toBig y
168    (J# s1 d1) .|. (J# s2 d2) = 
169         case orInteger# s1 d1 s2 d2 of
170           (# s, d #) -> J# s d
171    
172    (S# x) `xor` (S# y) = S# (word2Int# (int2Word# x `xor#` int2Word# y))
173    x@(S# _) `xor` y = toBig x `xor` y
174    x `xor` y@(S# _) = x `xor` toBig y
175    (J# s1 d1) `xor` (J# s2 d2) =
176         case xorInteger# s1 d1 s2 d2 of
177           (# s, d #) -> J# s d
178    
179    complement (S# x) = S# (word2Int# (int2Word# x `xor#` int2Word# (0# -# 1#)))
180    complement (J# s d) = case complementInteger# s d of (# s, d #) -> J# s d
181
182    shift x i | i >= 0    = x * 2^i
183              | otherwise = x `div` 2^(-i)
184
185    rotate x i = shift x i   -- since an Integer never wraps around
186
187    bitSize _  = error "Bits.bitSize(Integer)"
188    isSigned _ = True
189 #endif