[commit: ghc] wip/exceptions-note, wip/hadrian-import-packages, wip/splice-parsing, wip/trac-16270: Optimize pprASCII (d887f37)
git at git.haskell.org
git at git.haskell.org
Sat Feb 2 08:58:47 UTC 2019
Repository : ssh://git@git.haskell.org/ghc
On branches: wip/exceptions-note,wip/hadrian-import-packages,wip/splice-parsing,wip/trac-16270
Link : http://ghc.haskell.org/trac/ghc/changeset/d887f3749c4c9c0f30fb9805cf8953efbcd44b82/ghc
>---------------------------------------------------------------
commit d887f3749c4c9c0f30fb9805cf8953efbcd44b82
Author: Sylvain Henry <sylvain at haskus.fr>
Date: Fri Jan 18 00:01:45 2019 +0100
Optimize pprASCII
* Use `ByteString.foldr` instead of `(List.foldr . BS.unpack)`
* Avoid calling `chr` and its test that checks for invalid Unicode
codepoints: we stay in the ASCII range so we know we're ok
* Avoid calling `isPrint` (unsafe FFI call): we can check the ASCII
printable range directly
* Use bit operations (`unsafeShiftR`, `.&.`) instead of `div` and `mod`
>---------------------------------------------------------------
d887f3749c4c9c0f30fb9805cf8953efbcd44b82
compiler/nativeGen/PprBase.hs | 35 +++++++++++++++++++++++------------
1 file changed, 23 insertions(+), 12 deletions(-)
diff --git a/compiler/nativeGen/PprBase.hs b/compiler/nativeGen/PprBase.hs
index 4cdccee..afd16f8 100644
--- a/compiler/nativeGen/PprBase.hs
+++ b/compiler/nativeGen/PprBase.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE MagicHash #-}
+
-----------------------------------------------------------------------------
--
-- Pretty-printing assembly language
@@ -33,9 +35,11 @@ import Data.Array.ST
import Control.Monad.ST
import Data.Word
-import Data.Char
+import Data.Bits
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
+import GHC.Exts
+import GHC.Word
@@ -98,21 +102,28 @@ pprASCII str
-- the literal SDoc directly.
-- See Trac #14741
-- and Note [Pretty print ASCII when AsmCodeGen]
- = text $ foldr (\w s -> (do1 . fromIntegral) w ++ s) "" (BS.unpack str)
+ = text $ BS.foldr (\w s -> do1 w ++ s) "" str
where
- do1 :: Int -> String
- do1 w | '\t' <- chr w = "\\t"
- | '\n' <- chr w = "\\n"
- | '"' <- chr w = "\\\""
- | '\\' <- chr w = "\\\\"
- | isPrint (chr w) = [chr w]
+ do1 :: Word8 -> String
+ do1 w | 0x09 == w = "\\t"
+ | 0x0A == w = "\\n"
+ | 0x22 == w = "\\\""
+ | 0x5C == w = "\\\\"
+ -- ASCII printable characters range
+ | w >= 0x20 && w <= 0x7E = [chr' w]
| otherwise = '\\' : octal w
- octal :: Int -> String
- octal w = [ chr (ord '0' + (w `div` 64) `mod` 8)
- , chr (ord '0' + (w `div` 8) `mod` 8)
- , chr (ord '0' + w `mod` 8)
+ -- we know that the Chars we create are in the ASCII range
+ -- so we bypass the check in "chr"
+ chr' :: Word8 -> Char
+ chr' (W8# w#) = C# (chr# (word2Int# w#))
+
+ octal :: Word8 -> String
+ octal w = [ chr' (ord0 + (w `unsafeShiftR` 6) .&. 0x07)
+ , chr' (ord0 + (w `unsafeShiftR` 3) .&. 0x07)
+ , chr' (ord0 + w .&. 0x07)
]
+ ord0 = 0x30 -- = ord '0'
{-
Note [Pretty print ASCII when AsmCodeGen]
More information about the ghc-commits
mailing list