[commit: ghc] wip/T12357-unpack: Try fusing away unpackFS (6a317ee)
git at git.haskell.org
git at git.haskell.org
Tue Jul 5 08:00:19 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T12357-unpack
Link : http://ghc.haskell.org/trac/ghc/changeset/6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9/ghc
>---------------------------------------------------------------
commit 6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9
Author: Ben Gamari <ben at smart-cactus.org>
Date: Mon Jul 4 20:19:41 2016 -0400
Try fusing away unpackFS
>---------------------------------------------------------------
6a317ee95b04e3fdb4b4be6f710221aeb20d4ee9
compiler/utils/Encoding.hs | 17 ++++++++---------
compiler/utils/FastString.hs | 3 ++-
2 files changed, 10 insertions(+), 10 deletions(-)
diff --git a/compiler/utils/Encoding.hs b/compiler/utils/Encoding.hs
index 6028397..8da8831 100644
--- a/compiler/utils/Encoding.hs
+++ b/compiler/utils/Encoding.hs
@@ -35,7 +35,7 @@ import Numeric
import ExtsCompat46
import qualified Data.ByteString as BS
import qualified Data.ByteString.Unsafe as BS
-import System.IO.Unsafe ( unsafeInterleaveIO )
+import System.IO.Unsafe ( unsafePerformIO )
-- -----------------------------------------------------------------------------
-- UTF-8
@@ -114,19 +114,18 @@ utf8CharStart p = go p
then go (p `plusPtr` (-1))
else return p
-utf8DecodeStringLazy :: BS.ByteString -> IO [Char]
+utf8DecodeStringLazy :: BS.ByteString -> [Char]
utf8DecodeStringLazy !bs
- = unpack 0
+ = build (unpack 0)
where
- unpack !offset
- | BS.null bs' = return []
+ unpack !offset cons nil
+ | BS.null bs' = nil
| otherwise =
- BS.unsafeUseAsCString bs' $ \ptr ->
+ unsafePerformIO $ BS.unsafeUseAsCString bs' $ \ptr ->
case utf8DecodeChar (castPtr ptr) of
- (c, nBytes) -> do
- chs <- unsafeInterleaveIO $ unpack (offset + nBytes)
- return (c : chs)
+ (c, nBytes) -> return $ c `cons` unpack (offset + nBytes) cons nil
where !bs' = BS.drop offset bs
+{-# INLINEABLE utf8DecodeStringLazy #-}
utf8DecodeString :: Ptr Word8 -> Int -> IO [Char]
utf8DecodeString ptr len
diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs
index 21cbfeb..32330f2 100644
--- a/compiler/utils/FastString.hs
+++ b/compiler/utils/FastString.hs
@@ -482,7 +482,8 @@ nullFS f = BS.null (fs_bs f)
-- | Unpacks and decodes the FastString
unpackFS :: FastString -> String
-unpackFS (FastString _ _ bs _) = inlinePerformIO $ utf8DecodeStringLazy bs
+unpackFS (FastString _ _ bs _) = utf8DecodeStringLazy bs
+{-# INLINEABLE unpackFS #-}
-- | Gives the UTF-8 encoded bytes corresponding to a 'FastString'
bytesFS :: FastString -> [Word8]
More information about the ghc-commits
mailing list