d6a282fcbeab0b102fdc76f0c9378b062da678ed
[ghc-hetmet.git] / compiler / utils / FastFunctions.lhs
1 Z%
2 % (c) The University of Glasgow, 2000-2006
3 %
4 \section{Fast functions}
5
6 \begin{code}
7
8 module FastFunctions (
9     unsafeChr, inlinePerformIO, unsafeDupableInterleaveIO,
10     indexWord8OffFastPtr,
11     indexWord8OffFastPtrAsFastChar, indexWord8OffFastPtrAsFastInt,
12     global, Global
13   ) where
14
15 #include "HsVersions.h"
16
17 import FastTypes
18 import Data.IORef
19 import System.IO.Unsafe
20
21 #if defined(__GLASGOW_HASKELL__)
22
23 import GHC.Exts
24 import GHC.Word
25
26 #if __GLASGOW_HASKELL__ >= 611
27 import GHC.IO ( IO(..) )
28 #else
29 import GHC.IOBase ( IO(..) )
30 #endif
31
32 #if __GLASGOW_HASKELL__ >= 611
33 import GHC.IO (unsafeDupableInterleaveIO)
34 #else
35 import GHC.IOBase (unsafeDupableInterleaveIO)
36 #endif
37
38 import GHC.Base (unsafeChr)
39
40 -- Just like unsafePerformIO, but we inline it.
41 {-# INLINE inlinePerformIO #-}
42 inlinePerformIO :: IO a -> a
43 inlinePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r
44
45 indexWord8OffFastPtr p i = W8# (indexWord8OffAddr# p i)
46 indexWord8OffFastPtrAsFastChar p i = indexCharOffAddr# p i
47 indexWord8OffFastPtrAsFastInt p i = word2Int# (indexWord8OffAddr# p i)
48 -- or ord# (indexCharOffAddr# p i)
49
50 #else /* ! __GLASGOW_HASKELL__ */
51
52 import Foreign.Ptr
53 import Data.Word
54
55 -- hey, no harm inlining it, :-P
56 {-# INLINE inlinePerformIO #-}
57 inlinePerformIO :: IO a -> a
58 inlinePerformIO = unsafePerformIO
59
60 unsafeDupableInterleaveIO :: IO a -> IO a
61 unsafeDupableInterleaveIO = unsafeInterleaveIO
62
63 -- truly, these functions are unsafe: they assume
64 -- a certain immutability of the pointer's target area.
65 indexWord8OffFastPtr p i = inlinePerformIO (peekByteOff p n) :: Word8
66 indexWord8OffFastPtrAsFastInt p i =
67   iUnbox (fromIntegral (inlinePerformIO (peekByteOff p n) :: Word8))
68 indexWord8OffFastPtrAsFastChar p i =
69   fastChr (iUnbox (fromIntegral (inlinePerformIO (peekByteOff p n) :: Word8)))
70
71 #endif /* ! __GLASGOW_HASKELL__ */
72
73 --just so we can refer to the type clearly in a macro
74 type Global a = IORef a
75 global :: a -> Global a
76 global a = unsafePerformIO (newIORef a)
77
78 indexWord8OffFastPtr :: FastPtr Word8 -> FastInt -> Word8
79 indexWord8OffFastPtrAsFastChar :: FastPtr Word8 -> FastInt -> FastChar
80 indexWord8OffFastPtrAsFastInt :: FastPtr Word8 -> FastInt -> FastInt
81
82 \end{code}