summaryrefslogtreecommitdiff
path: root/ghc/compiler/utils/FastString.lhs
diff options
context:
space:
mode:
authorSimon Marlow <simonmar@microsoft.com>2006-02-08 13:10:18 +0000
committerSimon Marlow <simonmar@microsoft.com>2006-02-08 13:10:18 +0000
commit76e3742711eb9eb2fed7654c56e602b54c517e87 (patch)
treef8b04d68405880bd921bfb2da958058cd8c038ae /ghc/compiler/utils/FastString.lhs
parent3a4f9158d6d6688e591d505461d40e82c002c74c (diff)
downloadhaskell-76e3742711eb9eb2fed7654c56e602b54c517e87.tar.gz
add -dfaststring-stats to dump some stats about the FastString hash table
Diffstat (limited to 'ghc/compiler/utils/FastString.lhs')
-rw-r--r--ghc/compiler/utils/FastString.lhs25
1 files changed, 25 insertions, 0 deletions
diff --git a/ghc/compiler/utils/FastString.lhs b/ghc/compiler/utils/FastString.lhs
index 28aa6b0f31..4d432e6a75 100644
--- a/ghc/compiler/utils/FastString.lhs
+++ b/ghc/compiler/utils/FastString.lhs
@@ -51,6 +51,10 @@ module FastString
-- ** Outputing
hPutFS,
+ -- ** Internal
+ getFastStringTable,
+ hasZEncoding,
+
-- * LitStrings
LitString,
mkLitString#,
@@ -71,6 +75,7 @@ import System.IO.Unsafe ( unsafePerformIO )
import Control.Monad.ST ( stToIO )
import Data.IORef ( IORef, newIORef, readIORef, writeIORef )
import System.IO ( hPutBuf )
+import Data.Maybe ( isJust )
import GHC.Arr ( STArray(..), newSTArray )
import GHC.IOBase ( IO(..) )
@@ -343,6 +348,17 @@ isZEncoded :: FastString -> Bool
isZEncoded fs | ZEncoded <- enc fs = True
| otherwise = False
+-- | Returns 'True' if this 'FastString' is not Z-encoded but already has
+-- a Z-encoding cached (used in producing stats).
+hasZEncoding :: FastString -> Bool
+hasZEncoding fs@(FastString uid n_bytes _ fp enc) =
+ case enc of
+ ZEncoded -> False
+ UTF8Encoded ref ->
+ inlinePerformIO $ do
+ m <- readIORef ref
+ return (isJust m)
+
-- | Returns 'True' if the 'FastString' is empty
nullFS :: FastString -> Bool
nullFS f = n_bytes f == 0
@@ -415,6 +431,15 @@ uniqueOfFS (FastString (I# u#) _ _ _ _) = u#
nilFS = mkFastString ""
-- -----------------------------------------------------------------------------
+-- Stats
+
+getFastStringTable :: IO [[FastString]]
+getFastStringTable = do
+ tbl <- readIORef string_table
+ buckets <- mapM (lookupTbl tbl) [0..hASH_TBL_SIZE]
+ return buckets
+
+-- -----------------------------------------------------------------------------
-- Outputting 'FastString's
-- |Outputs a 'FastString' with /no decoding at all/, that is, you