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