[commit: ghc] wip/T12357: FastString: Add unpackFSLazy (11f802e)
git at git.haskell.org
git at git.haskell.org
Tue Jul 5 07:48:23 UTC 2016
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T12357
Link : http://ghc.haskell.org/trac/ghc/changeset/11f802e20c674f5d19b68e95e79cadd2ff1ab600/ghc
>---------------------------------------------------------------
commit 11f802e20c674f5d19b68e95e79cadd2ff1ab600
Author: Ben Gamari <ben at smart-cactus.org>
Date: Mon Jul 4 21:13:32 2016 -0400
FastString: Add unpackFSLazy
>---------------------------------------------------------------
11f802e20c674f5d19b68e95e79cadd2ff1ab600
compiler/utils/FastString.hs | 8 +++++++-
1 file changed, 7 insertions(+), 1 deletion(-)
diff --git a/compiler/utils/FastString.hs b/compiler/utils/FastString.hs
index f58a5b5..7f29eee 100644
--- a/compiler/utils/FastString.hs
+++ b/compiler/utils/FastString.hs
@@ -52,6 +52,7 @@ module FastString
-- ** Deconstruction
unpackFS, -- :: FastString -> String
+ unpackFSLazy, -- :: FastString -> String
bytesFS, -- :: FastString -> [Word8]
-- ** Encoding
@@ -482,7 +483,12 @@ nullFS f = BS.null (fs_bs f)
-- | Unpacks and decodes the FastString
unpackFS :: FastString -> String
-unpackFS (FastString _ _ bs _) = utf8DecodeStringLazy bs
+unpackFS (FastString _ _ bs _) =
+ inlinePerformIO $ BS.unsafeUseAsCStringLen bs $ \(ptr, len) ->
+ utf8DecodeString (castPtr ptr) len
+
+unpackFSLazy :: FastString -> String
+unpackFSLazy (FastString _ _ bs _) = utf8DecodeStringLazy bs
{-# INLINEABLE unpackFS #-}
-- | Gives the UTF-8 encoded bytes corresponding to a 'FastString'
More information about the ghc-commits
mailing list