[commit: ghc] master: Replace `STRICT[12345]` macros by `BangPatterns` (4af5748)
git at git.haskell.org
git at git.haskell.org
Tue Nov 25 17:27:31 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/4af5748b4589cb5a3c8fc389cc721ebb33260a56/ghc
>---------------------------------------------------------------
commit 4af5748b4589cb5a3c8fc389cc721ebb33260a56
Author: Yuri de Wit <admin at rodlogic.net>
Date: Tue Nov 25 18:22:34 2014 +0100
Replace `STRICT[12345]` macros by `BangPatterns`
This removes the macros `STRICT1()`, `STRICT2()`, `STRICT3()`,
`STRICT4()`, and `STRICT5()` CPP macros from `HsVersions.hs` and
replaces the few use sites by uses of `BangPatterns`.
Reviewed By: hvr
Differential Revision: https://phabricator.haskell.org/D525
>---------------------------------------------------------------
4af5748b4589cb5a3c8fc389cc721ebb33260a56
compiler/HsVersions.h | 8 --------
compiler/utils/BufWrite.hs | 20 +++-----------------
compiler/utils/Encoding.hs | 9 +++------
3 files changed, 6 insertions(+), 31 deletions(-)
diff --git a/compiler/HsVersions.h b/compiler/HsVersions.h
index 7ba82e1..6d5716d 100644
--- a/compiler/HsVersions.h
+++ b/compiler/HsVersions.h
@@ -49,13 +49,5 @@ name = Util.globalM (value);
#define ASSERTM2(e,msg) do { bool <- e; MASSERT2(bool,msg) }
#define WARNM2(e,msg) do { bool <- e; WARN(bool, msg) return () }
--- Useful for declaring arguments to be strict
-#define STRICT1(f) f a | a `seq` False = undefined
-#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
-#define STRICT4(f) f a b c d | a `seq` b `seq` c `seq` d `seq` False = undefined
-#define STRICT5(f) f a b c d e | a `seq` b `seq` c `seq` d `seq` e `seq` False = undefined
-#define STRICT6(f) f a b c d e f | a `seq` b `seq` c `seq` d `seq` e `seq` f `seq` False = undefined
-
#endif /* HsVersions.h */
diff --git a/compiler/utils/BufWrite.hs b/compiler/utils/BufWrite.hs
index 482e9ee..40b9759 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 5c8619b..ae727d2 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
More information about the ghc-commits
mailing list