[Git][ghc/ghc][wip/mono-local-binds] Turn on -XMonoLocalBinds by default
Sebastian Graf
gitlab at gitlab.haskell.org
Mon Jul 6 12:31:54 UTC 2020
Sebastian Graf pushed to branch wip/mono-local-binds at Glasgow Haskell Compiler / GHC
Commits:
d216a2c8 by Sebastian Graf at 2020-07-06T14:31:10+02:00
Turn on -XMonoLocalBinds by default
And fix the resulting type errors.
- - - - -
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
=====================================
@@ -202,7 +202,7 @@ regAlloc _ (CmmProc _ _ _ _)
-- an entry in the block map or it is the first block.
--
linearRegAlloc
- :: (Outputable instr, Instruction instr)
+ :: forall instr . (Outputable instr, Instruction instr)
=> NCGConfig
-> [BlockId] -- ^ entry points
-> BlockMap RegSet
@@ -228,6 +228,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
@@ -953,4 +955,3 @@ loadTemp vreg (ReadMem slot) hreg spills
loadTemp _ _ _ spills =
return spills
-
=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -2320,6 +2320,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
=====================================
@@ -1940,7 +1940,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
=====================================
@@ -1366,7 +1366,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)
@@ -1408,8 +1409,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
=====================================
@@ -1132,6 +1132,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
=====================================
@@ -8,7 +8,7 @@
-----------------------------------------------------------------------------
-}
-{-# LANGUAGE CPP, MultiWayIf, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, MultiWayIf, ScopedTypeVariables, NoMonoLocalBinds #-}
module GHC.SysTools (
-- * Initialisation
@@ -141,6 +141,7 @@ lazyInitLlvmConfig top_dir
passes <- readAndParse "llvm-passes" id
return $ LlvmConfig { llvmTargets = targets, llvmPasses = passes }
where
+ -- This one has a really complicated type, hence -XNoMonoLocalBinds
readAndParse name builder =
do let llvmConfigFile = top_dir </> name
llvmConfigStr <- readFile llvmConfigFile
=====================================
compiler/ghc.cabal.in
=====================================
@@ -153,6 +153,7 @@ Library
-- we use an explicit Prelude
Default-Extensions:
NoImplicitPrelude
+ MonoLocalBinds
Exposed-Modules:
GHC.Iface.Ext.Types
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d216a2c818235cfa1cbd0756b146223e08430d59
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d216a2c818235cfa1cbd0756b146223e08430d59
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/20200706/39c73b40/attachment-0001.html>
More information about the ghc-commits
mailing list