Skip to content

Commit

Permalink
Revert "Revert "Optimize isSpace functions (haskell#315)""
Browse files Browse the repository at this point in the history
This reverts commit cc2287b.
  • Loading branch information
Bodigrim committed Feb 15, 2021
1 parent cc2287b commit d54623d
Showing 1 changed file with 12 additions and 17 deletions.
29 changes: 12 additions & 17 deletions Data/ByteString/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -139,6 +139,7 @@ import Data.String (IsString(..))

import Control.Exception (assert)

import Data.Bits ((.&.))
import Data.Char (ord)
import Data.Word

Expand Down Expand Up @@ -737,28 +738,22 @@ c2w = fromIntegral . ord
{-# INLINE c2w #-}

-- | Selects words corresponding to white-space characters in the Latin-1 range
-- ordered by frequency.
isSpaceWord8 :: Word8 -> Bool
isSpaceWord8 w =
w == 0x20 ||
w == 0x0A || -- LF, \n
w == 0x09 || -- HT, \t
w == 0x0C || -- FF, \f
w == 0x0D || -- CR, \r
w == 0x0B || -- VT, \v
w == 0xA0 -- spotted by QC..
isSpaceWord8 w8 =
-- Avoid the cost of narrowing arithmetic results to Word8,
-- the conversion from Word8 to Word is free.
let w :: Word
!w = fromIntegral w8
in w .&. 0x50 == 0 -- Quick non-whitespace filter
&& w - 0x21 > 0x7e -- Second non-whitespace filter
&& ( w == 0x20 -- SP
|| w == 0xa0 -- NBSP
|| w - 0x09 < 5) -- HT, NL, VT, FF, CR
{-# INLINE isSpaceWord8 #-}

-- | Selects white-space characters in the Latin-1 range
isSpaceChar8 :: Char -> Bool
isSpaceChar8 c =
c == ' ' ||
c == '\t' ||
c == '\n' ||
c == '\r' ||
c == '\f' ||
c == '\v' ||
c == '\xa0'
isSpaceChar8 = isSpaceWord8 . c2w
{-# INLINE isSpaceChar8 #-}

overflowError :: String -> a
Expand Down

0 comments on commit d54623d

Please sign in to comment.