[commit: packages/bytestring] master, wip/nix-local-build: Fix breakByte and spanByte rewrite rules (4b97b6d)

git at git.haskell.org git at git.haskell.org
Tue May 3 22:44:07 UTC 2016


Repository : ssh://git@git.haskell.org/bytestring

On branches: master,wip/nix-local-build
Link       : http://git.haskell.org/packages/bytestring.git/commitdiff/4b97b6d0854c86f5c7acf3df40d5e22a0acf74e4

>---------------------------------------------------------------

commit 4b97b6d0854c86f5c7acf3df40d5e22a0acf74e4
Author: Ben Gamari <ben at smart-cactus.org>
Date:   Tue Mar 8 17:53:50 2016 +0100

    Fix breakByte and spanByte rewrite rules
    
    Previously these were matching on (==), which was rewritten by the class
    op rule before the breakByte rule had an opportunity to fire (#70).
    Unfortunately fixing this requires that we change the Eq instances
    provided by GHC. This has been done in GHC 8.0.1 (base-4.9.0).


>---------------------------------------------------------------

4b97b6d0854c86f5c7acf3df40d5e22a0acf74e4
 Data/ByteString.hs       | 36 ++++++++++++++++++++++++++++--------
 Data/ByteString/Char8.hs | 18 ++++++++++++++++--
 2 files changed, 44 insertions(+), 10 deletions(-)

diff --git a/Data/ByteString.hs b/Data/ByteString.hs
index 9d73593..54d96e7 100644
--- a/Data/ByteString.hs
+++ b/Data/ByteString.hs
@@ -852,12 +852,22 @@ break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
 break p ps = case findIndexOrEnd p ps of n -> (unsafeTake n ps, unsafeDrop n ps)
 {-# INLINE [1] break #-}
 
+-- See bytestring #70
+#if MIN_VERSION_base(4,9,0)
 {-# RULES
-"ByteString specialise break (x==)" forall x.
-    break ((==) x) = breakByte x
-"ByteString specialise break (==x)" forall x.
-    break (==x) = breakByte x
+"ByteString specialise break (x ==)" forall x.
+    break (x `eqWord8`) = breakByte x
+"ByteString specialise break (== x)" forall x.
+    break (`eqWord8` x) = breakByte x
   #-}
+#else
+{-# RULES
+"ByteString specialise break (x ==)" forall x.
+    break (x ==) = breakByte x
+"ByteString specialise break (== x)" forall x.
+    break (== x) = breakByte x
+  #-}
+#endif
 
 -- INTERNAL:
 
@@ -905,12 +915,22 @@ spanByte c ps@(PS x s l) =
                                   else go p (i+1)
 {-# INLINE spanByte #-}
 
+-- See bytestring #70
+#if MIN_VERSION_base(4,9,0)
 {-# RULES
-"ByteString specialise span (x==)" forall x.
-    span ((==) x) = spanByte x
-"ByteString specialise span (==x)" forall x.
-    span (==x) = spanByte x
+"ByteString specialise span (x ==)" forall x.
+    span (x `eqWord8`) = spanByte x
+"ByteString specialise span (== x)" forall x.
+    span (`eqWord8` x) = spanByte x
   #-}
+#else
+{-# RULES
+"ByteString specialise span (x ==)" forall x.
+    span (x ==) = spanByte x
+"ByteString specialise span (== x)" forall x.
+    span (== x) = spanByte x
+  #-}
+#endif
 
 -- | 'spanEnd' behaves like 'span' but from the end of the 'ByteString'.
 -- We have
diff --git a/Data/ByteString/Char8.hs b/Data/ByteString/Char8.hs
index c153655..2f7c250 100644
--- a/Data/ByteString/Char8.hs
+++ b/Data/ByteString/Char8.hs
@@ -257,6 +257,10 @@ import Data.ByteString (empty,null,length,tail,init,append
 import Data.ByteString.Internal
 
 import Data.Char    ( isSpace )
+#if MIN_VERSION_base(4,9,0)
+-- See bytestring #70
+import GHC.Char (eqChar)
+#endif
 import qualified Data.List as List (intersperse)
 
 import System.IO    (Handle,stdout,openBinaryFile,hClose,hFileSize,IOMode(..))
@@ -508,12 +512,22 @@ break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString)
 break f = B.break (f . w2c)
 {-# INLINE [1] break #-}
 
+-- See bytestring #70
+#if MIN_VERSION_base(4,9,0)
+{-# RULES
+"ByteString specialise break (x==)" forall x.
+    break (x `eqChar`) = breakChar x
+"ByteString specialise break (==x)" forall x.
+    break (`eqChar` x) = breakChar x
+  #-}
+#else
 {-# RULES
 "ByteString specialise break (x==)" forall x.
-    break ((==) x) = breakChar x
+    break (x ==) = breakChar x
 "ByteString specialise break (==x)" forall x.
-    break (==x) = breakChar x
+    break (== x) = breakChar x
   #-}
+#endif
 
 -- INTERNAL:
 



More information about the ghc-commits mailing list