Make some profiling flags dynamic
[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 import GHC.IOBase (IO(..))
26 --why not import it at __GLASGOW_HASKELL__==606 ?
27 #if __GLASGOW_HASKELL__ >= 607
28 import GHC.IOBase (unsafeDupableInterleaveIO)
29 #endif
30 import GHC.Base (unsafeChr)
31
32 #if __GLASGOW_HASKELL__ < 607
33 unsafeDupableInterleaveIO :: IO a -> IO a
34 unsafeDupableInterleaveIO = unsafeInterleaveIO
35 #endif
36
37 -- Just like unsafePerformIO, but we inline it.
38 {-# INLINE inlinePerformIO #-}
39 inlinePerformIO :: IO a -> a
40 inlinePerformIO (IO m) = case m realWorld# of (# _, r #)   -> r
41
42 indexWord8OffFastPtr p i = W8# (indexWord8OffAddr# p i)
43 indexWord8OffFastPtrAsFastChar p i = indexCharOffAddr# p i
44 indexWord8OffFastPtrAsFastInt p i = word2Int# (indexWord8OffAddr# p i)
45 -- or ord# (indexCharOffAddr# p i)
46
47 #else /* ! __GLASGOW_HASKELL__ */
48
49 import Foreign.Ptr
50 import Data.Word
51
52 -- hey, no harm inlining it, :-P
53 {-# INLINE inlinePerformIO #-}
54 inlinePerformIO :: IO a -> a
55 inlinePerformIO = unsafePerformIO
56
57 unsafeDupableInterleaveIO :: IO a -> IO a
58 unsafeDupableInterleaveIO = unsafeInterleaveIO
59
60 -- truly, these functions are unsafe: they assume
61 -- a certain immutability of the pointer's target area.
62 indexWord8OffFastPtr p i = inlinePerformIO (peekByteOff p n) :: Word8
63 indexWord8OffFastPtrAsFastInt p i =
64   iUnbox (fromIntegral (inlinePerformIO (peekByteOff p n) :: Word8))
65 indexWord8OffFastPtrAsFastChar p i =
66   fastChr (iUnbox (fromIntegral (inlinePerformIO (peekByteOff p n) :: Word8)))
67
68 #endif /* ! __GLASGOW_HASKELL__ */
69
70 --just so we can refer to the type clearly in a macro
71 type Global a = IORef a
72 global :: a -> Global a
73 global a = unsafePerformIO (newIORef a)
74
75 indexWord8OffFastPtr :: FastPtr Word8 -> FastInt -> Word8
76 indexWord8OffFastPtrAsFastChar :: FastPtr Word8 -> FastInt -> FastChar
77 indexWord8OffFastPtrAsFastInt :: FastPtr Word8 -> FastInt -> FastInt
78
79 \end{code}