Skip to content

Commit

Permalink
Fix breakByte and spanByte rewrite rules
Browse files Browse the repository at this point in the history
Previously these were matching on (==), which was rewritten by the class
op rule before the breakByte rule had an opportunity to fire (haskell#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).
  • Loading branch information
bgamari committed Mar 28, 2016
1 parent d562ea9 commit 8515aa8
Show file tree
Hide file tree
Showing 2 changed files with 43 additions and 9 deletions.
34 changes: 27 additions & 7 deletions Data/ByteString.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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:

Expand Down Expand Up @@ -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.
"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
"ByteString specialise span (== x)" forall x.
span (== x) = spanByte x
#-}
#endif

-- | 'spanEnd' behaves like 'span' but from the end of the 'ByteString'.
-- We have
Expand Down
18 changes: 16 additions & 2 deletions Data/ByteString/Char8.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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(..))
Expand Down Expand Up @@ -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:

Expand Down

0 comments on commit 8515aa8

Please sign in to comment.