summaryrefslogtreecommitdiff
path: root/compiler/utils
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/utils')
-rw-r--r--compiler/utils/BufWrite.hs20
-rw-r--r--compiler/utils/Encoding.hs9
2 files changed, 6 insertions, 23 deletions
diff --git a/compiler/utils/BufWrite.hs b/compiler/utils/BufWrite.hs
index 482e9eee42..40b9759a7b 100644
--- a/compiler/utils/BufWrite.hs
+++ b/compiler/utils/BufWrite.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
-----------------------------------------------------------------------------
--
@@ -23,8 +23,6 @@ module BufWrite (
bFlush,
) where
-#include "HsVersions.h"
-
import FastString
import FastTypes
import FastMutInt
@@ -53,12 +51,8 @@ newBufHandle hdl = do
buf_size :: Int
buf_size = 8192
-#define STRICT2(f) f a b | a `seq` b `seq` False = undefined
-#define STRICT3(f) f a b c | a `seq` b `seq` c `seq` False = undefined
-
bPutChar :: BufHandle -> Char -> IO ()
-STRICT2(bPutChar)
-bPutChar b@(BufHandle buf r hdl) c = do
+bPutChar b@(BufHandle buf r hdl) !c = do
i <- readFastMutInt r
if (i >= buf_size)
then do hPutBuf hdl buf buf_size
@@ -68,8 +62,7 @@ bPutChar b@(BufHandle buf r hdl) c = do
writeFastMutInt r (i+1)
bPutStr :: BufHandle -> String -> IO ()
-STRICT2(bPutStr)
-bPutStr (BufHandle buf r hdl) str = do
+bPutStr (BufHandle buf r hdl) !str = do
i <- readFastMutInt r
loop str i
where loop _ i | i `seq` False = undefined
@@ -124,10 +117,3 @@ bFlush (BufHandle buf r hdl) = do
when (i > 0) $ hPutBuf hdl buf i
free buf
return ()
-
-#if 0
-myPutBuf s hdl buf i =
- modifyIOError (\e -> ioeSetErrorString e (ioeGetErrorString e ++ ':':s ++ " (" ++ show buf ++ "," ++ show i ++ ")")) $
-
- hPutBuf hdl buf i
-#endif
diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs
index 5c8619baa6..ae727d2f3f 100644
--- a/compiler/utils/Encoding.hs
+++ b/compiler/utils/Encoding.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples #-}
+{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples #-}
{-# OPTIONS_GHC -O #-}
-- We always optimise this, otherwise performance of a non-optimised
-- compiler is severely affected
@@ -28,7 +28,6 @@ module Encoding (
zDecodeString
) where
-#include "HsVersions.h"
import Foreign
import Data.Char
import Numeric
@@ -169,16 +168,14 @@ utf8EncodeChar c ptr =
utf8EncodeString :: Ptr Word8 -> String -> IO ()
utf8EncodeString ptr str = go ptr str
- where STRICT2(go)
- go _ [] = return ()
+ where go !_ [] = return ()
go ptr (c:cs) = do
ptr' <- utf8EncodeChar c ptr
go ptr' cs
utf8EncodedLength :: String -> Int
utf8EncodedLength str = go 0 str
- where STRICT2(go)
- go n [] = n
+ where go !n [] = n
go n (c:cs)
| ord c > 0 && ord c <= 0x007f = go (n+1) cs
| ord c <= 0x07ff = go (n+2) cs