[Git][ghc/ghc][wip/js-staging] Compactor: remove dead code
Sylvain Henry (@hsyl20)
gitlab at gitlab.haskell.org
Fri Oct 14 10:24:08 UTC 2022
Sylvain Henry pushed to branch wip/js-staging at Glasgow Haskell Compiler / GHC
Commits:
cf1d7dcd by Sylvain Henry at 2022-10-14T12:27:28+02:00
Compactor: remove dead code
- - - - -
2 changed files:
- compiler/GHC/StgToJS/Linker/Compactor.hs
- compiler/GHC/StgToJS/Linker/Types.hs
Changes:
=====================================
compiler/GHC/StgToJS/Linker/Compactor.hs
=====================================
@@ -32,7 +32,6 @@
module GHC.StgToJS.Linker.Compactor
( compact
- , collectGlobals
, debugShowStat
, packStrings
, staticInfoArgs
@@ -76,11 +75,6 @@ import Prelude
import GHC.Utils.Encoding
--- | collect global objects (data / CAFs). rename them and add them to the table
-collectGlobals :: [StaticInfo]
- -> State CompactorState ()
-collectGlobals = mapM_ (\(StaticInfo i _ _) -> renameObj i)
-
debugShowStat :: (JStat, [ClosureInfo], [StaticInfo]) -> String
debugShowStat (_s, cis, sis) =
"closures:\n" ++
@@ -173,42 +167,10 @@ staticDeclStat (StaticInfo global_name static_value _) = decl
to_byte_list = JList . map (Int . fromIntegral) . BS.unpack
--- | rename a heap object, which means adding it to the
--- static init table in addition to the renamer
-renameObj :: FastString
- -> State CompactorState FastString
-renameObj xs = do
- (TxtI xs') <- renameVar (TxtI xs) -- added to the renamer
- modify (addStaticEntry xs') -- and now the table
- return xs'
-
lookupRenamed :: CompactorState -> Ident -> Ident
lookupRenamed cs i@(TxtI t) =
fromMaybe i (lookupUniqMap (csNameMap cs) t)
-renameVar :: Ident -- ^ text identifier to rename
- -> State CompactorState Ident -- ^ the updated renamer state and the new ident
-renameVar i@(TxtI t)
- | "h$$" `List.isPrefixOf` unpackFS t = do
- m <- gets csNameMap
- case lookupUniqMap m t of
- Just r -> return r
- Nothing -> do
- y <- newIdent
- let add_var cs' = cs' {csNameMap = addToUniqMap (csNameMap cs') t y}
- modify add_var
- return y
- | otherwise = return i
-
-newIdent :: State CompactorState Ident
-newIdent = do
- yys <- gets csIdentSupply
- case yys of
- (y:ys) -> do
- modify (\cs -> cs {csIdentSupply = ys})
- return y
- _ -> error "newIdent: empty list"
-
-- | rename a compactor info entry according to the compactor state (no new renamings are added)
renameClosureInfo :: CompactorState
-> ClosureInfo
=====================================
compiler/GHC/StgToJS/Linker/Types.hs
=====================================
@@ -43,23 +43,12 @@ import System.IO
import Prelude
--- | Return a list of fresh local @Ident@
---
--- Prefix them with 'h$$' such that these will be compacted by the compactor.
-newLocals :: [Ident]
-newLocals = mkIdents 0
- where
- mkIdent s = TxtI (mkFastString ("h$$" <> s))
- mkIdents n = [mkIdent (c0:cs) | c0 <- chars, cs <- replicateM n chars] ++ mkIdents (n+1)
- chars = ['0'..'9'] ++ ['a'..'z'] ++ ['A'..'Z']
-
--------------------------------------------------------------------------------
-- CompactorState
--------------------------------------------------------------------------------
data CompactorState = CompactorState
- { csIdentSupply :: ![Ident] -- ^ ident supply for new names
- , csNameMap :: !(UniqMap FastString Ident) -- ^ renaming mapping for internal names
+ { csNameMap :: !(UniqMap FastString Ident) -- ^ renaming mapping for internal names
, csEntries :: !(UniqMap FastString Int) -- ^ entry functions (these get listed in the metadata init
-- array)
, csNumEntries :: !Int
@@ -85,18 +74,19 @@ data StringTable = StringTable
-- | The empty @CompactorState@
emptyCompactorState :: CompactorState
-emptyCompactorState = CompactorState newLocals
- mempty
- mempty
- 0
- mempty
- 0
- mempty
- 0
- mempty
- mempty
- mempty
- emptyStringTable
+emptyCompactorState = CompactorState
+ { csNameMap = mempty
+ , csEntries = mempty
+ , csNumEntries = 0
+ , csStatics = mempty
+ , csNumStatics = 0
+ , csLabels = mempty
+ , csNumLabels = 0
+ , csParentEntries = mempty
+ , csParentStatics = mempty
+ , csParentLabels = mempty
+ , csStringTable = emptyStringTable
+ }
-- | The empty @StringTable@
emptyStringTable :: StringTable
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf1d7dcdc7fb9c03eb7fe771ba4f6ee7b4389b0b
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf1d7dcdc7fb9c03eb7fe771ba4f6ee7b4389b0b
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221014/4df8dc9b/attachment-0001.html>
More information about the ghc-commits
mailing list