~ubuntu-branches/ubuntu/precise/ghc/precise

« back to all changes in this revision

Viewing changes to compiler/utils/FastTypes.lhs

  • Committer: Bazaar Package Importer
  • Author(s): Joachim Breitner
  • Date: 2011-01-17 12:49:24 UTC
  • Revision ID: james.westby@ubuntu.com-20110117124924-do1pym1jlf5o636m
Tags: upstream-7.0.1
ImportĀ upstreamĀ versionĀ 7.0.1

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%
 
2
% (c) The University of Glasgow, 2000-2006
 
3
%
 
4
\section{Fast integers, etc... booleans moved to FastBool for using panic}
 
5
 
 
6
\begin{code}
 
7
 
 
8
--Even if the optimizer could handle boxed arithmetic equally well,
 
9
--this helps automatically check the sources to make sure that
 
10
--it's only used in an appropriate pattern of efficiency.
 
11
--(it also makes `let`s and `case`s stricter...)
 
12
 
 
13
-- | Fast integers, characters and pointer types for use in many parts of GHC
 
14
module FastTypes (
 
15
    -- * FastInt
 
16
    FastInt,
 
17
    
 
18
    -- ** Getting in and out of FastInt
 
19
    _ILIT, iBox, iUnbox,
 
20
    
 
21
    -- ** Arithmetic on FastInt
 
22
    (+#), (-#), (*#), quotFastInt, negateFastInt,
 
23
    --quotRemFastInt is difficult because unboxed values can't
 
24
    --be tupled, but unboxed tuples aren't portable.  Just use
 
25
    -- nuisance boxed quotRem and rely on optimization.
 
26
    (==#), (/=#), (<#), (<=#), (>=#), (>#),
 
27
    minFastInt, maxFastInt,
 
28
    --prefer to distinguish operations, not types, between
 
29
    --signed and unsigned.
 
30
    --left-shift is the same for 'signed' and 'unsigned' numbers
 
31
    shiftLFastInt,
 
32
    --right-shift isn't the same for negative numbers (ones with
 
33
    --the highest-order bit '1').  If you don't care because the
 
34
    --number you're shifting is always nonnegative, use the '_' version
 
35
    --which should just be the fastest one.
 
36
    shiftR_FastInt,
 
37
    --"L' = logical or unsigned shift; 'A' = arithmetic or signed shift
 
38
    shiftRLFastInt, shiftRAFastInt,
 
39
    bitAndFastInt, bitOrFastInt,
 
40
    --add more operations to this file as you need them
 
41
 
 
42
    -- * FastChar
 
43
    FastChar,
 
44
 
 
45
    -- ** Getting in and out of FastChar
 
46
    _CLIT, cBox, cUnbox,
 
47
 
 
48
    -- ** Operations on FastChar
 
49
    fastOrd, fastChr, eqFastChar,
 
50
    --note, fastChr is "unsafe"Chr: it doesn't check for
 
51
    --character values above the range of Unicode
 
52
 
 
53
    -- * FastPtr
 
54
    FastPtr, 
 
55
    
 
56
    -- ** Getting in and out of FastPtr
 
57
    pBox, pUnbox,
 
58
    
 
59
    -- ** Casting FastPtrs
 
60
    castFastPtr
 
61
  ) where
 
62
 
 
63
#include "HsVersions.h"
 
64
 
 
65
#if defined(__GLASGOW_HASKELL__)
 
66
 
 
67
-- Import the beggars
 
68
import GHC.Exts
 
69
 
 
70
type FastInt = Int#
 
71
 
 
72
--in case it's a macro, don't lexically feed an argument!
 
73
--e.g. #define _ILIT(x) (x#) , #define _ILIT(x) (x :: FastInt)
 
74
_ILIT = \(I# x) -> x
 
75
--perhaps for accomodating caseless-leading-underscore treatment,
 
76
--something like _iLIT or iLIT would be better?
 
77
 
 
78
iBox x = I# x
 
79
iUnbox (I# x) = x
 
80
quotFastInt   = quotInt#
 
81
negateFastInt = negateInt#
 
82
 
 
83
--I think uncheckedIShiftL# and uncheckedIShiftRL# are the same
 
84
--as uncheckedShiftL# and uncheckedShiftRL# ...
 
85
--should they be used? How new are they?
 
86
--They existed as far back as GHC 6.0 at least...
 
87
shiftLFastInt x y = uncheckedIShiftL# x y
 
88
shiftR_FastInt x y = uncheckedIShiftRL# x y
 
89
shiftRLFastInt x y = uncheckedIShiftRL# x y
 
90
shiftRAFastInt x y = uncheckedIShiftRA# x y
 
91
--{-# INLINE shiftLNonnegativeFastInt #-}
 
92
--{-# INLINE shiftRNonnegativeFastInt #-}
 
93
--shiftLNonnegativeFastInt n p = word2Int#((int2Word# n) `uncheckedShiftL#` p)
 
94
--shiftRNonnegativeFastInt n p = word2Int#((int2Word# n) `uncheckedShiftRL#` p)
 
95
bitAndFastInt x y = word2Int# (and# (int2Word# x) (int2Word# y))
 
96
bitOrFastInt x y = word2Int# (or# (int2Word# x) (int2Word# y))
 
97
 
 
98
type FastChar = Char#
 
99
_CLIT = \(C# c) -> c
 
100
cBox c = C# c
 
101
cUnbox (C# c) = c
 
102
fastOrd c = ord# c
 
103
fastChr x = chr# x
 
104
eqFastChar a b = eqChar# a b
 
105
 
 
106
--note that the type-parameter doesn't provide any safety
 
107
--when it's a synonym, but as long as we keep it compiling
 
108
--with and without __GLASGOW_HASKELL__ defined, it's fine.
 
109
type FastPtr a = Addr#
 
110
pBox p = Ptr p
 
111
pUnbox (Ptr p) = p
 
112
castFastPtr p = p
 
113
 
 
114
#else /* ! __GLASGOW_HASKELL__ */
 
115
 
 
116
import Data.Char (ord, chr)
 
117
 
 
118
import Data.Bits
 
119
import Data.Word (Word) --is it a good idea to assume this exists too?
 
120
--does anyone need shiftRLFastInt? (apparently yes.)
 
121
 
 
122
import Foreign.Ptr
 
123
 
 
124
type FastInt = Int
 
125
_ILIT x = x
 
126
iBox x = x
 
127
iUnbox x = x
 
128
(+#) = (+)
 
129
(-#) = (-)
 
130
(*#) = (*)
 
131
quotFastInt   = quot
 
132
--quotRemFastInt = quotRem
 
133
negateFastInt = negate
 
134
(==#) = (==)
 
135
(/=#) = (/=)
 
136
(<#)  = (<)
 
137
(<=#) = (<=)
 
138
(>=#) = (>=)
 
139
(>#)  = (>)
 
140
shiftLFastInt = shiftL
 
141
shiftR_FastInt = shiftR
 
142
shiftRAFastInt = shiftR
 
143
shiftRLFastInt n p = fromIntegral (shiftR (fromIntegral n :: Word) p)
 
144
--shiftLFastInt n p = n * (2 ^ p)
 
145
--assuming quot-Int is faster and the
 
146
--same for nonnegative arguments than div-Int
 
147
--shiftR_FastInt n p = n `quot` (2 ^ p)
 
148
--shiftRAFastInt n p = n `div` (2 ^ p)
 
149
--I couldn't figure out how to implement without Word nor Bits
 
150
--shiftRLFastInt n p = fromIntegral ((fromIntegral n :: Word) `quot` (2 ^ (fromIntegral p :: Word)))
 
151
 
 
152
bitAndFastInt = (.&.)
 
153
bitOrFastInt = (.|.)
 
154
 
 
155
type FastBool = Bool
 
156
fastBool x = x
 
157
isFastTrue x = x
 
158
-- make sure these are as strict as the unboxed version,
 
159
-- so that the performance characteristics match
 
160
fastOr False False = False
 
161
fastOr _ _ = True
 
162
fastAnd True True = True
 
163
fastAnd _ _ = False
 
164
 
 
165
type FastChar = Char
 
166
_CLIT c = c
 
167
cBox c = c
 
168
cUnbox c = c
 
169
fastOrd = ord
 
170
fastChr = chr  --or unsafeChr if there was a standard location for it
 
171
eqFastChar = (==)
 
172
 
 
173
type FastPtr a = Ptr a
 
174
pBox p = p
 
175
pUnbox p = p
 
176
castFastPtr = castPtr
 
177
 
 
178
--These are among the type-signatures necessary for !ghc to compile
 
179
-- but break ghc (can't give a signature for an import...)
 
180
--Note that the comparisons actually do return Bools not FastBools.
 
181
(+#), (-#), (*#) :: FastInt -> FastInt -> FastInt
 
182
(==#), (/=#), (<#), (<=#), (>=#), (>#) :: FastInt -> FastInt -> Bool
 
183
 
 
184
#endif /* ! __GLASGOW_HASKELL__ */
 
185
 
 
186
minFastInt, maxFastInt :: FastInt -> FastInt -> FastInt
 
187
minFastInt x y = if x <# y then x else y
 
188
maxFastInt x y = if x <# y then y else x
 
189
 
 
190
-- type-signatures will improve the non-ghc-specific versions
 
191
-- and keep things accurate (and ABLE to compile!)
 
192
_ILIT :: Int -> FastInt
 
193
iBox :: FastInt -> Int
 
194
iUnbox :: Int -> FastInt
 
195
 
 
196
quotFastInt :: FastInt -> FastInt -> FastInt
 
197
negateFastInt :: FastInt -> FastInt
 
198
shiftLFastInt, shiftR_FastInt, shiftRAFastInt, shiftRLFastInt
 
199
   :: FastInt -> FastInt -> FastInt
 
200
bitAndFastInt, bitOrFastInt :: FastInt -> FastInt -> FastInt
 
201
 
 
202
_CLIT :: Char -> FastChar
 
203
cBox :: FastChar -> Char
 
204
cUnbox :: Char -> FastChar
 
205
fastOrd :: FastChar -> FastInt
 
206
fastChr :: FastInt -> FastChar
 
207
eqFastChar :: FastChar -> FastChar -> Bool
 
208
 
 
209
pBox :: FastPtr a -> Ptr a
 
210
pUnbox :: Ptr a -> FastPtr a
 
211
castFastPtr :: FastPtr a -> FastPtr b
 
212
 
 
213
\end{code}