[project @ 2002-02-12 11:44:54 by simonmar]
[ghc-hetmet.git] / ghc / lib / std / PrelBits.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1998-2000
3 %
4 \section[Bits]{The @Bits@ interface}
5
6 Defines the @Bits@ class containing bit-based operations.
7 See library document for details on the semantics of the
8 individual operations.
9
10 \begin{code}
11 {-# OPTIONS -fno-implicit-prelude #-}
12 #include "MachDeps.h"
13
14 module PrelBits where
15
16 #ifdef __GLASGOW_HASKELL__
17 import PrelGHC
18 import PrelBase
19 import PrelNum
20 #endif
21
22 --ADR: The fixity for .|. conflicts with that for .|. in Fran.
23 --     Removing all fixities is a fairly safe fix; fixing the "one fixity
24 --     per symbol per program" limitation in Hugs would take a lot longer.
25 #ifndef __HUGS__
26 infixl 8 `shift`, `rotate`, `shiftL`, `shiftR`, `rotateL`, `rotateR`
27 infixl 7 .&.
28 infixl 6 `xor`
29 infixl 5 .|.
30 #endif
31
32 class Num a => Bits a where
33     (.&.), (.|.), xor :: a -> a -> a
34     complement        :: a -> a
35     shift             :: a -> Int -> a
36     rotate            :: a -> Int -> a
37     bit               :: Int -> a
38     setBit            :: a -> Int -> a
39     clearBit          :: a -> Int -> a
40     complementBit     :: a -> Int -> a
41     testBit           :: a -> Int -> Bool
42     bitSize           :: a -> Int
43     isSigned          :: a -> Bool
44
45     bit i               = 1 `shift` i
46     x `setBit` i        = x .|. bit i
47     x `clearBit` i      = x .&. complement (bit i)
48     x `complementBit` i = x `xor` bit i
49     x `testBit` i       = (x .&. bit i) /= 0
50
51 shiftL, shiftR   :: Bits a => a -> Int -> a
52 rotateL, rotateR :: Bits a => a -> Int -> a
53 x `shiftL`  i = x `shift`  i
54 x `shiftR`  i = x `shift`  (-i)
55 x `rotateL` i = x `rotate` i
56 x `rotateR` i = x `rotate` (-i)
57
58 instance Bits Int where
59     (I# x#) .&.   (I# y#)  = I# (word2Int# (int2Word# x# `and#` int2Word# y#))
60     (I# x#) .|.   (I# y#)  = I# (word2Int# (int2Word# x# `or#`  int2Word# y#))
61     (I# x#) `xor` (I# y#)  = I# (word2Int# (int2Word# x# `xor#` int2Word# y#))
62     complement (I# x#)     = I# (word2Int# (int2Word# x# `xor#` int2Word# (-1#)))
63     (I# x#) `shift` (I# i#)
64         | i# ==# 0#     = I# x#
65         | i# >=# wsib   = 0
66         | i# ># 0#      = I# (x# `uncheckedIShiftL#` i#)
67         | i# <=# nwsib  = I# (if x# <# 0# then -1# else 0#)
68         | otherwise     = I# (x# `uncheckedIShiftRA#` negateInt# i#)
69           where
70              wsib  = WORD_SIZE_IN_BITS#   {- work around preprocessor problem (??) -}
71              nwsib = negateInt# wsib
72     (I# x#) `rotate` (I# i#) =
73         I# (word2Int# ((x'# `uncheckedShiftL#` i'#) `or#`
74                        (x'# `uncheckedShiftRL#` (wsib -# i'#))))
75         where
76            x'#   = int2Word# x#
77            i'#   = word2Int# (int2Word# i# `and#` int2Word# (wsib -# 1#))
78            wsib  = WORD_SIZE_IN_BITS#
79     bitSize  _                 = WORD_SIZE_IN_BITS
80     isSigned _                 = True
81 \end{code}