[Git][ghc/ghc][wip/con-info] 2 commits: fix warnings

Matthew Pickering gitlab at gitlab.haskell.org
Mon Jun 8 15:26:48 UTC 2020



Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC


Commits:
869f2754 by Matthew Pickering at 2020-06-08T16:26:18+01:00
fix warnings

- - - - -
fe2bc4b0 by Matthew Pickering at 2020-06-08T16:26:29+01:00
Warnings

- - - - -


10 changed files:

- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Pipeline.hs
- compiler/GHC/Driver/CodeOutput.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/StgToCmm.hs
- compiler/GHC/StgToCmm/Bind.hs
- compiler/GHC/StgToCmm/Heap.hs
- compiler/GHC/StgToCmm/Monad.hs
- compiler/GHC/StgToCmm/Prof.hs
- rts/Trace.c


Changes:

=====================================
compiler/GHC/Cmm/CLabel.hs
=====================================
@@ -13,7 +13,6 @@
 module GHC.Cmm.CLabel (
         CLabel, -- abstract type
         ForeignLabelSource(..),
-        InfoTableEnt(..),
         pprDebugCLabel,
 
         mkClosureLabel,
@@ -387,7 +386,7 @@ pprDebugCLabel :: CLabel -> SDoc
 pprDebugCLabel lbl
  = case lbl of
         IdLabel _ _ info-> ppr lbl <> (parens $ text "IdLabel")
-                                       -- <> whenPprDebug (text ":" <> text (show info)))
+                                        <> whenPprDebug (text ":" <> ppr info)
         CmmLabel pkg _name _info
          -> ppr lbl <> (parens $ text "CmmLabel" <+> ppr pkg)
 
@@ -426,6 +425,23 @@ data IdLabelInfo
 
   deriving (Eq, Ord)
 
+instance Outputable IdLabelInfo where
+  ppr Closure    = text "Closure"
+  ppr InfoTable  = text "InfoTable"
+  ppr Entry      = text "Entry"
+  ppr Slow       = text "Slow"
+
+  ppr LocalInfoTable  = text "LocalInfoTable"
+  ppr LocalEntry      = text "LocalEntry"
+
+  ppr RednCounts      = text "RednCounts"
+
+  ppr (ConEntry mn) = text "ConEntry" <+> ppr mn
+  ppr (ConInfoTable mn) = text "ConInfoTable" <+> ppr mn
+  ppr ClosureTable = text "ClosureTable"
+  ppr Bytes        = text "Bytes"
+  ppr BlockInfoTable  = text "BlockInfoTable"
+
 
 data RtsLabelInfo
   = RtsSelectorInfoTable Bool{-updatable-} Int{-offset-}  -- ^ Selector thunks


=====================================
compiler/GHC/Cmm/Pipeline.hs
=====================================
@@ -21,7 +21,6 @@ import GHC.Cmm.ContFlowOpt
 import GHC.Cmm.LayoutStack
 import GHC.Cmm.Sink
 import GHC.Cmm.Dataflow.Collections
-import GHC.Types.Name.Set
 
 import GHC.Types.Unique.Supply
 import GHC.Driver.Session


=====================================
compiler/GHC/Driver/CodeOutput.hs
=====================================
@@ -42,13 +42,11 @@ import GHC.Utils.Outputable
 import GHC.Unit
 import GHC.Types.SrcLoc
 import GHC.Types.CostCentre
-import GHC.Types.Name.Set
 
 import Control.Exception
 import System.Directory
 import System.FilePath
 import System.IO
-import Data.IORef
 
 {-
 ************************************************************************


=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -138,7 +138,6 @@ import GHC.Cmm.Parser       ( parseCmmFile )
 import GHC.Cmm.Info.Build
 import GHC.Cmm.Pipeline
 import GHC.Cmm.Info
-import GHC.Cmm.CLabel
 import GHC.Driver.CodeOutput
 import GHC.Core.InstEnv
 import GHC.Core.FamInstEnv
@@ -168,7 +167,6 @@ import GHC.Utils.Misc
 
 import Data.List        ( nub, isPrefixOf, partition )
 import Control.Monad
-import Data.IORef
 import System.FilePath as FilePath
 import System.Directory
 import System.IO (fixIO)
@@ -182,8 +180,6 @@ import GHC.Iface.Ext.Ast    ( mkHieFile )
 import GHC.Iface.Ext.Types  ( getAsts, hie_asts, hie_module )
 import GHC.Iface.Ext.Binary ( readHieFile, writeHieFile , hie_file_result)
 import GHC.Iface.Ext.Debug  ( diffFile, validateScopes )
-import GHC.Types.Unique.Map
-import GHC.Core.DataCon
 
 #include "HsVersions.h"
 


=====================================
compiler/GHC/StgToCmm.hs
=====================================
@@ -48,7 +48,6 @@ import GHC.Types.Basic
 import GHC.Types.Var.Set ( isEmptyDVarSet )
 import GHC.SysTools.FileCleanup
 import GHC.Types.Unique.FM
-import GHC.Types.Name.Set
 
 import GHC.Data.OrdList
 import GHC.Cmm.Graph
@@ -60,7 +59,6 @@ import System.IO.Unsafe
 import qualified Data.ByteString as BS
 import GHC.Types.Unique.Map
 import GHC.Types.SrcLoc
-import Data.Maybe
 
 
 codeGen :: DynFlags
@@ -74,7 +72,7 @@ codeGen :: DynFlags
         -> Stream IO CmmGroup ()       -- Output as a stream, so codegen can
                                        -- be interleaved with output
 
-codeGen dflags this_mod ip_map@(InfoTableProvMap (dcmap@(UniqMap denv)) _) data_tycons
+codeGen dflags this_mod ip_map@(InfoTableProvMap ((UniqMap denv)) _) data_tycons
         cost_centre_info stg_binds hpc_info lref
   = do  {     -- cg: run the code generator, and yield the resulting CmmGroup
               -- Using an IORef to store the state is a bit crude, but otherwise
@@ -97,7 +95,7 @@ codeGen dflags this_mod ip_map@(InfoTableProvMap (dcmap@(UniqMap denv)) _) data_
                -- FIRST.  This is because when -split-objs is on we need to
                -- combine this block with its initialisation routines; see
                -- Note [pipeline-split-init].
-        ; cg (mkModuleInit cost_centre_info this_mod hpc_info [])
+        ; cg (mkModuleInit cost_centre_info this_mod hpc_info)
 
         ; mapM_ (cg . cgTopBinding dflags) stg_binds
         ; cgs <- liftIO (readIORef  cgref)
@@ -191,13 +189,11 @@ mkModuleInit
         :: CollectedCCs         -- cost centre info
         -> Module
         -> HpcInfo
-        -> [InfoTableEnt]
         -> FCode ()
 
-mkModuleInit cost_centre_info this_mod hpc_info info_ents
+mkModuleInit cost_centre_info this_mod hpc_info
   = do  { initHpc this_mod hpc_info
         ; initCostCentres cost_centre_info
-       -- ; initInfoTableProv info_ents
         }
 
 


=====================================
compiler/GHC/StgToCmm/Bind.hs
=====================================
@@ -89,11 +89,11 @@ cgTopRhsClosure dflags rec id ccs upd_flag args body =
   -- hole detection from working in that case.  Test
   -- concurrent/should_run/4030 fails, for instance.
   --
-  --gen_code _ _ closure_label
-  -- | StgApp f [] <- body, null args, isNonRec rec
-  -- = do
-  --      cg_info <- getCgIdInfo f
-   --      emitDataCon closure_label indStaticInfoTable ccs [unLit (idInfoToAmode cg_info)]
+  gen_code _ _ closure_label
+   | StgApp f [] <- body, null args, isNonRec rec
+   = do
+        cg_info <- getCgIdInfo f
+        emitDataCon closure_label indStaticInfoTable ccs [unLit (idInfoToAmode cg_info)]
 
   gen_code dflags lf_info _closure_label
    = do { let name = idName id


=====================================
compiler/GHC/StgToCmm/Heap.hs
=====================================
@@ -48,12 +48,11 @@ import GHC.Unit
 import GHC.Driver.Session
 import GHC.Platform
 import GHC.Data.FastString( mkFastString, fsLit )
-import GHC.Utils.Panic( sorry )
 
 import Control.Monad (when)
 import Data.Maybe (isJust)
 import GHC.Utils.Outputable
-import GHC.Stack (HasCallStack, callStack)
+import GHC.Stack (HasCallStack)
 
 -----------------------------------------------------------
 --              Initialise dynamic heap objects


=====================================
compiler/GHC/StgToCmm/Monad.hs
=====================================
@@ -82,8 +82,6 @@ import GHC.Data.FastString
 import GHC.Utils.Outputable
 import GHC.Utils.Misc
 import GHC.Types.SrcLoc
-import GHC.Types.Name.Set
-import GHC.Types.Unique.FM
 
 import Control.Monad
 import Data.List


=====================================
compiler/GHC/StgToCmm/Prof.hs
=====================================
@@ -44,11 +44,6 @@ import GHC.Driver.Session
 import GHC.Data.FastString
 import GHC.Unit.Module as Module
 import GHC.Utils.Outputable
-import GHC.Types.Var.Env
-import GHC.Types.Unique.FM
-import GHC.Types.Unique.Set
-import Control.Monad.IO.Class
-import Data.IORef
 
 import Control.Monad
 import Data.Char (ord)
@@ -282,17 +277,12 @@ sizeof_ccs_words dflags
 initInfoTableProv ::  InfoTableProvMap -> Module -> FCode ()
 -- Emit the declarations
 initInfoTableProv (InfoTableProvMap dcmap clmap) this_mod
-  = do dflags <- getDynFlags
-       binds <- getBinds
+  = do
        infos <- getUsedInfo
-
        let ents = (((convertDCMap this_mod dcmap))
                    ++ (convertClosureMap infos this_mod clmap))
-       pprTraceM "binds" (ppr (sizeUFM binds))
-
-       pprTraceM "UsedInfo" (ppr (length infos))
-
-       pprTraceM "initInfoTable" (ppr (length ents))
+       --pprTraceM "UsedInfo" (ppr (length infos))
+       --pprTraceM "initInfoTable" (ppr (length ents))
        mapM_ emitInfoTableProv ents
 
 --- Info Table Prov stuff


=====================================
rts/Trace.c
=====================================
@@ -651,7 +651,7 @@ void traceIPE(StgInfoTable * info,
               const char *srcloc )
 {
     if (eventlog_enabled) {
-        postIPE(info, table_name, closure_desc, label, module, srcloc);
+        postIPE(INFO_PTR_TO_STRUCT(info), table_name, closure_desc, label, module, srcloc);
     }
 }
 



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b27ea3e7f630331db271d2c6664a210fde0c56c8...fe2bc4b047ae775946b586457d3686b940d66559

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b27ea3e7f630331db271d2c6664a210fde0c56c8...fe2bc4b047ae775946b586457d3686b940d66559
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/20200608/59b4a188/attachment-0001.html>


More information about the ghc-commits mailing list