[Git][ghc/ghc][master] Turn on -XMonoLocalBinds by default (#18430)
Marge Bot
gitlab at gitlab.haskell.org
Wed Sep 2 19:55:02 UTC 2020
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00
Turn on -XMonoLocalBinds by default (#18430)
And fix the resulting type errors.
Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com>
Metric Decrease:
parsing001
- - - - -
7 changed files:
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Opt/Simplify.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Runtime/Linker.hs
- compiler/GHC/SysTools.hs
- compiler/ghc.cabal.in
Changes:
=====================================
compiler/GHC/CmmToAsm/Reg/Linear.hs
=====================================
@@ -205,7 +205,7 @@ regAlloc _ (CmmProc _ _ _ _)
-- an entry in the block map or it is the first block.
--
linearRegAlloc
- :: Instruction instr
+ :: forall instr. Instruction instr
=> NCGConfig
-> [BlockId] -- ^ entry points
-> BlockMap RegSet
@@ -231,6 +231,8 @@ linearRegAlloc config entry_ids block_live sccs
ArchJavaScript -> panic "linearRegAlloc ArchJavaScript"
ArchUnknown -> panic "linearRegAlloc ArchUnknown"
where
+ go :: (FR regs, Outputable regs)
+ => regs -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int)
go f = linearRegAlloc' config f entry_ids block_live sccs
platform = ncgPlatform config
@@ -973,4 +975,3 @@ loadTemp vreg (ReadMem slot) hreg spills
loadTemp _ _ _ spills =
return spills
-
=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -2290,6 +2290,7 @@ lintCoercion this@(AxiomRuleCo ax cos)
Nothing -> err "Malformed use of AxiomRuleCo" [ ppr this ]
Just _ -> return (AxiomRuleCo ax cos') }
where
+ err :: forall a. String -> [SDoc] -> LintM a
err m xs = failWithL $
hang (text m) 2 $ vcat (text "Rule:" <+> ppr (coaxrName ax) : xs)
=====================================
compiler/GHC/Core/Opt/Simplify.hs
=====================================
@@ -1909,7 +1909,7 @@ completeCall env var cont
log_inlining $
sep [text "Inlining done:", nest 4 (ppr var)]
| otherwise
- = liftIO $ log_inlining $
+ = log_inlining $
sep [text "Inlining done: " <> ppr var,
nest 4 (vcat [text "Inlined fn: " <+> nest 2 (ppr unfolding),
text "Cont: " <+> ppr cont])]
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1373,7 +1373,8 @@ parUpsweep_one mod home_mod_map comp_graph_loops lcl_dflags mHscMessage cleanup
--
-- There better had not be any cyclic groups here -- we check for them.
upsweep
- :: GhcMonad m
+ :: forall m
+ . GhcMonad m
=> Maybe Messager
-> HomePackageTable -- ^ HPT from last time round (pruned)
-> StableModules -- ^ stable modules (see checkStability)
@@ -1415,8 +1416,7 @@ upsweep mHscMessage old_hpt stable_mods cleanup sccs = do
return (Failed, done')
upsweep'
- :: GhcMonad m
- => HomePackageTable
+ :: HomePackageTable
-> ModuleGraph
-> [SCC ModSummary]
-> Int
=====================================
compiler/GHC/Runtime/Linker.hs
=====================================
@@ -1134,6 +1134,7 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do
-- Note that we want to remove all *local*
-- (i.e. non-isExternal) names too (these are the
-- temporary bindings from the command line).
+ keep_name :: (Name, a) -> Bool
keep_name (n,_) = isExternalName n &&
nameModule n `elemModuleSet` bcos_retained
=====================================
compiler/GHC/SysTools.hs
=====================================
@@ -138,15 +138,17 @@ lazyInitLlvmConfig :: String
-> IO LlvmConfig
lazyInitLlvmConfig top_dir
= unsafeInterleaveIO $ do -- see Note [LLVM configuration]
- targets <- readAndParse "llvm-targets" mkLlvmTarget
- passes <- readAndParse "llvm-passes" id
- return $ LlvmConfig { llvmTargets = targets, llvmPasses = passes }
+ targets <- readAndParse "llvm-targets"
+ passes <- readAndParse "llvm-passes"
+ return $ LlvmConfig { llvmTargets = fmap mkLlvmTarget <$> targets,
+ llvmPasses = passes }
where
- readAndParse name builder =
+ readAndParse :: Read a => String -> IO a
+ readAndParse name =
do let llvmConfigFile = top_dir </> name
llvmConfigStr <- readFile llvmConfigFile
case maybeReadFuzzy llvmConfigStr of
- Just s -> return (fmap builder <$> s)
+ Just s -> return s
Nothing -> pgmError ("Can't parse " ++ show llvmConfigFile)
mkLlvmTarget :: (String, String, String) -> LlvmTarget
=====================================
compiler/ghc.cabal.in
=====================================
@@ -153,6 +153,7 @@ Library
NoImplicitPrelude
,BangPatterns
,ScopedTypeVariables
+ ,MonoLocalBinds
Exposed-Modules:
GHC.Iface.Ext.Types
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bfab2a30be5cc68e7914c3f6bb9ae4ad33283ffc
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bfab2a30be5cc68e7914c3f6bb9ae4ad33283ffc
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/20200902/b6b7feee/attachment-0001.html>
More information about the ghc-commits
mailing list