
[Git][ghc/ghc][master] driver: Use ModuleGraph for oneshot and --make mode
by Marge Bot (@marge-bot) 16 Apr '25
by Marge Bot (@marge-bot) 16 Apr '25
16 Apr '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
d47bf776 by Matthew Pickering at 2025-04-14T16:44:41+01:00
driver: Use ModuleGraph for oneshot and --make mode
This patch uses the `hsc_mod_graph` field for both oneshot and --make
mode. Therefore, if part of the compiler requires usage of the module
graph, you do so in a uniform way for the two different modes.
The `ModuleGraph` describes the relationship between the modules in the
home package and units in external packages. The `ModuleGraph` can be
queried when information about the transitive closure of a package is
needed. For example, the primary use of the ModuleGraph from within the
compiler is in the loader, which needs to know the transitive closure of
a module so it can load all the relevant objects for evaluation.
In --make mode, downsweep computes the ModuleGraph before any
compilation starts.
In oneshot mode, a thunk is created at the start of compilation, which
when forced will compute the module graph beneath the current module.
The thunk is only forced at the moment when the user uses Template
Haskell.
Finally, there are some situations where we need to discover what
dependencies to load but haven't loaded a module graph at all. In this
case, there is a fallback which computes the transitive closure on the
fly and doesn't cache the result. Presumably if you are going to call
getLinkDeps a lot, you would compute the right ModuleGraph before you
started.
Importantly, this removes the ExternalModuleGraph abstraction. This was quite
awkward to work with since it stored information about the home package
inside the EPS.
This patch will also be very useful when implementing explicit level
imports, which requires more significant use of the module graph in
order to determine which level instances are available at.
Towards #25795
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
-------------------------
- - - - -
26 changed files:
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeAction.hs
- + compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Pipeline.hs-boot
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Unit/External.hs
- compiler/GHC/Unit/Finder.hs
- − compiler/GHC/Unit/Module/External/Graph.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/ModNodeKey.hs
- compiler/ghc.cabal.in
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs
Changes:
=====================================
compiler/GHC/Driver/Downsweep.hs
=====================================
@@ -10,9 +10,14 @@
{-# LANGUAGE ViewPatterns #-}
module GHC.Driver.Downsweep
( downsweep
+ , downsweepThunk
+ , downsweepInstalledModules
+ , downsweepFromRootNodes
+ , DownsweepMode(..)
-- * Summary functions
, summariseModule
, summariseFile
+ , summariseModuleInterface
, SummariseResult(..)
-- * Helper functions
, instantiationNodes
@@ -21,33 +26,37 @@ module GHC.Driver.Downsweep
import GHC.Prelude
-import GHC.Tc.Utils.Backpack
-
-
import GHC.Platform.Ways
import GHC.Driver.Config.Finder (initFinderOpts)
import GHC.Driver.Config.Parser (initParserOpts)
import GHC.Driver.Phases
-import GHC.Driver.Pipeline
+import {-# SOURCE #-} GHC.Driver.Pipeline (preprocess)
import GHC.Driver.Session
import GHC.Driver.Backend
import GHC.Driver.Monad
import GHC.Driver.Env
import GHC.Driver.Errors
import GHC.Driver.Errors.Types
-import GHC.Driver.Main
+import GHC.Driver.Messager
import GHC.Driver.MakeSem
import GHC.Driver.MakeAction
+import GHC.Driver.Config.Diagnostic
+import GHC.Driver.Ppr
-import GHC.Parser.Header
+import GHC.Iface.Load
+import GHC.Parser.Header
+import GHC.Rename.Names
+import GHC.Tc.Utils.Backpack
import GHC.Data.Graph.Directed
import GHC.Data.FastString
import GHC.Data.Maybe ( expectJust )
+import qualified GHC.Data.Maybe as M
import GHC.Data.OsPath ( unsafeEncodeUtf )
import GHC.Data.StringBuffer
+import GHC.Data.Graph.Directed.Reachability
import qualified GHC.LanguageExtensions as LangExt
import GHC.Utils.Exception ( throwIO, SomeAsyncException )
@@ -58,6 +67,7 @@ import GHC.Utils.Error
import GHC.Utils.Logger
import GHC.Utils.Fingerprint
import GHC.Utils.TmpFs
+import GHC.Utils.Constants
import GHC.Types.Error
import GHC.Types.Target
@@ -71,7 +81,10 @@ import GHC.Unit
import GHC.Unit.Env
import GHC.Unit.Finder
import GHC.Unit.Module.ModSummary
+import GHC.Unit.Module.ModIface
import GHC.Unit.Module.Graph
+import GHC.Unit.Module.Deps
+import qualified GHC.Unit.Home.Graph as HUG
import Data.Either ( rights, partitionEithers, lefts )
import qualified Data.Map as Map
@@ -82,6 +95,7 @@ import Control.Monad
import Control.Monad.Trans.Except ( ExceptT(..), runExceptT, throwE )
import qualified Control.Monad.Catch as MC
import Data.Maybe
+import Data.List (partition)
import Data.Time
import Data.List (unfoldr)
import Data.Bifunctor (first)
@@ -91,19 +105,45 @@ import System.FilePath
import Control.Monad.Trans.Reader
import qualified Data.Map.Strict as M
import Control.Monad.Trans.Class
-import GHC.Rename.Names
-import GHC.Utils.Constants
+import System.IO.Unsafe (unsafeInterleaveIO)
-import GHC.Data.Graph.Directed.Reachability
-import qualified GHC.Unit.Home.Graph as HUG
+{-
+Note [Downsweep and the ModuleGraph]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+The ModuleGraph stores the relationship between all the modules, units, and
+instantiations in the current session.
+
+When we do downsweep, we build up a new ModuleGraph, starting from the root
+modules. By following all the dependencies we construct a graph which allows
+us to answer questions about the transitive closure of the imports.
+
+The module graph is accessible in the HscEnv.
+
+When is this graph constructed?
+
+1. In `--make` mode, we construct the graph before starting to do any compilation.
+
+2. In `-c` (oneshot) mode, we construct the graph when we have calculated the
+ ModSummary for the module we are compiling. The `ModuleGraph` is stored in a
+ thunk, so it is only constructed when it is needed. This avoids reading
+ the interface files of the whole transitive closure unless they are needed.
+
+3. In some situations (such as loading plugins) we may need to construct the
+ graph without having a ModSummary. In this case we use the `downsweepInstalledModules`
+ function.
+
+The result is having a uniform graph available for the whole compilation pipeline.
+
+-}
-- This caches the answer to the question, if we are in this unit, what does
-- an import of this module mean.
-type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either DriverMessages ModSummary]
+type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either DriverMessages ModuleNodeInfo]
-----------------------------------------------------------------------------
--
--- | Downsweep (dependency analysis)
+-- | Downsweep (dependency analysis) for --make mode
--
-- Chase downwards from the specified root set, returning summaries
-- for all home modules encountered. Only follow source-import
@@ -113,9 +153,15 @@ type DownsweepCache = M.Map (UnitId, PkgQual, ModuleNameWithIsBoot) [Either Driv
-- cache to avoid recalculating a module summary if the source is
-- unchanged.
--
--- The returned list of [ModSummary] nodes has one node for each home-package
+-- The returned ModuleGraph has one node for each home-package
-- module, plus one for any hs-boot files. The imports of these nodes
-- are all there, including the imports of non-home-package modules.
+--
+-- This function is intendned for use by --make mode and will also insert
+-- LinkNodes and InstantiationNodes for any home units.
+--
+-- It will also turn on code generation for any modules that need it by calling
+-- 'enableCodeGenForTH'.
downsweep :: HscEnv
-> (GhcMessage -> AnyGhcDiagnostic)
-> Maybe Messager
@@ -132,8 +178,31 @@ downsweep :: HscEnv
-- which case there can be repeats
downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do
n_jobs <- mkWorkerLimit (hsc_dflags hsc_env)
- new <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary
- downsweep_imports hsc_env old_summary_map excl_mods allow_dup_roots new
+ (root_errs, root_summaries) <- rootSummariesParallel n_jobs hsc_env diag_wrapper msg summary
+ let closure_errs = checkHomeUnitsClosed unit_env
+ unit_env = hsc_unit_env hsc_env
+
+ all_errs = closure_errs ++ root_errs
+
+ case all_errs of
+ [] -> do
+ (downsweep_errs, downsweep_nodes) <- downsweepFromRootNodes hsc_env old_summary_map excl_mods allow_dup_roots DownsweepUseCompile (map ModuleNodeCompile root_summaries) []
+
+ let (other_errs, unit_nodes) = partitionEithers $ HUG.unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env)
+
+ let all_nodes = downsweep_nodes ++ unit_nodes
+ let all_errs = downsweep_errs ++ other_errs
+
+ let logger = hsc_logger hsc_env
+ tmpfs = hsc_tmpfs hsc_env
+ -- if we have been passed -fno-code, we enable code generation
+ -- for dependencies of modules that have -XTemplateHaskell,
+ -- otherwise those modules will fail to compile.
+ -- See Note [-fno-code mode] #8025
+ th_configured_nodes <- enableCodeGenForTH logger tmpfs unit_env all_nodes
+
+ return (all_errs, th_configured_nodes)
+ _ -> return (all_errs, emptyMG)
where
summary = getRootSummary excl_mods old_summary_map
@@ -146,47 +215,102 @@ downsweep hsc_env diag_wrapper msg old_summaries excl_mods allow_dup_roots = do
old_summary_map =
M.fromList [((ms_unitid ms, msHsFilePath ms), ms) | ms <- old_summaries]
-downsweep_imports :: HscEnv
+ -- Dependencies arising on a unit (backpack and module linking deps)
+ unitModuleNodes :: [ModuleGraphNode] -> UnitId -> HomeUnitEnv -> [Either (Messages DriverMessage) ModuleGraphNode]
+ unitModuleNodes summaries uid hue =
+ maybeToList (linkNodes summaries uid hue)
+
+-- | Calculate the module graph starting from a single ModSummary. The result is a
+-- thunk, which when forced will perform the downsweep. This is useful in oneshot
+-- mode where the module graph may never be needed.
+-- If downsweep fails, then the resulting errors are just thrown.
+downsweepThunk :: HscEnv -> ModSummary -> IO ModuleGraph
+downsweepThunk hsc_env mod_summary = unsafeInterleaveIO $ do
+ debugTraceMsg (hsc_logger hsc_env) 3 $ text "Computing Module Graph thunk..."
+ ~(errs, mg) <- downsweepFromRootNodes hsc_env mempty [] True DownsweepUseFixed [ModuleNodeCompile mod_summary] []
+ let dflags = hsc_dflags hsc_env
+ liftIO $ printOrThrowDiagnostics (hsc_logger hsc_env)
+ (initPrintConfig dflags)
+ (initDiagOpts dflags)
+ (GhcDriverMessage <$> unionManyMessages errs)
+ return (mkModuleGraph mg)
+
+-- | Create a module graph from a list of installed modules.
+-- This is used by the loader when we need to load modules but there
+-- isn't already an existing module graph. For example, when loading plugins
+-- during initialisation.
+--
+-- If you call this function, then if the `Module` you request to downsweep can't
+-- be found then this function will throw errors.
+-- If you need to use this function elsewhere, then it would make sense to make it
+-- return [DriverMessages] and [ModuleGraph] so that the caller can handle the errors as it sees fit.
+-- At the moment, it is overfitted for what `get_reachable_nodes` needs.
+downsweepInstalledModules :: HscEnv -> [Module] -> IO ModuleGraph
+downsweepInstalledModules hsc_env mods = do
+ let
+ (home_mods, external_mods) = partition (\u -> moduleUnitId u `elem` hsc_all_home_unit_ids hsc_env) mods
+ installed_mods = map (fst . getModuleInstantiation) home_mods
+ external_uids = map moduleUnitId external_mods
+
+ process :: InstalledModule -> IO ModuleNodeInfo
+ process i = do
+ res <- findExactModule hsc_env i NotBoot
+ case res of
+ InstalledFound loc -> return $ ModuleNodeFixed (installedModuleToMnk i) loc
+ -- It is an internal-ish error if this happens, since we any call to this function should
+ -- already know that we can find the modules we need to load.
+ _ -> throwGhcException $ ProgramError $ showSDoc (hsc_dflags hsc_env) $ text "downsweepInstalledModules: Could not find installed module" <+> ppr i
+
+ nodes <- mapM process installed_mods
+ (errs, mg) <- downsweepFromRootNodes hsc_env mempty [] True DownsweepUseFixed nodes external_uids
+
+ -- Similarly here, we should really not get any errors, but print them out if we do.
+ let dflags = hsc_dflags hsc_env
+ liftIO $ printOrThrowDiagnostics (hsc_logger hsc_env)
+ (initPrintConfig dflags)
+ (initDiagOpts dflags)
+ (GhcDriverMessage <$> unionManyMessages errs)
+
+ return (mkModuleGraph mg)
+
+
+
+-- | Whether downsweep should use compiler or fixed nodes. Compile nodes are used
+-- by --make mode, and fixed nodes by oneshot mode.
+--
+-- See Note [Module Types in the ModuleGraph] for the difference between the two.
+data DownsweepMode = DownsweepUseCompile | DownsweepUseFixed
+
+-- | Perform downsweep, starting from the given root 'ModuleNodeInfo's and root
+-- 'UnitId's.
+-- This function will start at the given roots, and traverse downwards to find
+-- all the dependencies, all the way to the leaf units.
+downsweepFromRootNodes :: HscEnv
-> M.Map (UnitId, FilePath) ModSummary
-> [ModuleName]
-> Bool
- -> ([(UnitId, DriverMessages)], [ModSummary])
- -> IO ([DriverMessages], ModuleGraph)
-downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, rootSummariesOk)
+ -> DownsweepMode -- ^ Whether to create fixed or compile nodes for dependencies
+ -> [ModuleNodeInfo] -- ^ The starting ModuleNodeInfo
+ -> [UnitId] -- ^ The starting units
+ -> IO ([DriverMessages], [ModuleGraphNode])
+downsweepFromRootNodes hsc_env old_summaries excl_mods allow_dup_roots mode root_nodes root_uids
= do
- let root_map = mkRootMap rootSummariesOk
+ let root_map = mkRootMap root_nodes
checkDuplicates root_map
- (deps, map0) <- loopSummaries rootSummariesOk (M.empty, root_map)
+ (module_deps, map0) <- loopModuleNodeInfos root_nodes (M.empty, root_map)
+ let all_deps = loopUnit hsc_env module_deps root_uids
+
let all_instantiations = getHomeUnitInstantiations hsc_env
- let deps' = loopInstantiations all_instantiations deps
- let closure_errs = checkHomeUnitsClosed unit_env
- unit_env = hsc_unit_env hsc_env
- tmpfs = hsc_tmpfs hsc_env
+ let deps' = loopInstantiations all_instantiations all_deps
downsweep_errs = lefts $ concat $ M.elems map0
downsweep_nodes = M.elems deps'
- (other_errs, unit_nodes) = partitionEithers $ HUG.unitEnv_foldWithKey (\nodes uid hue -> nodes ++ unitModuleNodes downsweep_nodes uid hue) [] (hsc_HUG hsc_env)
- all_nodes = downsweep_nodes ++ unit_nodes
- all_errs = all_root_errs ++ downsweep_errs ++ other_errs
- all_root_errs = closure_errs ++ map snd root_errs
-
- -- if we have been passed -fno-code, we enable code generation
- -- for dependencies of modules that have -XTemplateHaskell,
- -- otherwise those modules will fail to compile.
- -- See Note [-fno-code mode] #8025
- th_enabled_nodes <- enableCodeGenForTH logger tmpfs unit_env all_nodes
- if null all_root_errs
- then return (all_errs, th_enabled_nodes)
- else pure $ (all_root_errs, emptyMG)
+ return (downsweep_errs, downsweep_nodes)
where
getHomeUnitInstantiations :: HscEnv -> [(UnitId, InstantiatedUnit)]
getHomeUnitInstantiations hsc_env = HUG.unitEnv_foldWithKey (\nodes uid hue -> nodes ++ instantiationNodes uid (homeUnitEnv_units hue)) [] (hsc_HUG hsc_env)
- -- Dependencies arising on a unit (backpack and module linking deps)
- unitModuleNodes :: [ModuleGraphNode] -> UnitId -> HomeUnitEnv -> [Either (Messages DriverMessage) ModuleGraphNode]
- unitModuleNodes summaries uid hue =
- maybeToList (linkNodes summaries uid hue)
calcDeps ms =
-- Add a dependency on the HsBoot file if it exists
@@ -195,8 +319,6 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
[(ms_unitid ms, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
[(ms_unitid ms, b, c) | (b, c) <- msDeps ms ]
- logger = hsc_logger hsc_env
-
-- In a root module, the filename is allowed to diverge from the module
-- name, so we have to check that there aren't multiple root files
-- defining the same module (otherwise the duplicates will be silently
@@ -209,7 +331,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
, dup_root:_ <- dup_roots = liftIO $ multiRootsErr dup_root
| otherwise = pure ()
where
- dup_roots :: [[ModSummary]] -- Each at least of length 2
+ dup_roots :: [[ModuleNodeInfo]] -- Each at least of length 2
dup_roots = filterOut isSingleton $ map rights (M.elems root_map)
loopInstantiations :: [(UnitId, InstantiatedUnit)]
@@ -250,6 +372,102 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
| otherwise
= Nothing
+ loopModuleNodeInfos :: [ModuleNodeInfo] -> (M.Map NodeKey ModuleGraphNode, DownsweepCache) -> IO (M.Map NodeKey ModuleGraphNode, DownsweepCache)
+ loopModuleNodeInfos is cache = foldM (flip loopModuleNodeInfo) cache is
+
+ loopModuleNodeInfo :: ModuleNodeInfo -> (M.Map NodeKey ModuleGraphNode, DownsweepCache) -> IO (M.Map NodeKey ModuleGraphNode, DownsweepCache)
+ loopModuleNodeInfo mod_node_info (done, summarised) = do
+ case mod_node_info of
+ ModuleNodeCompile ms -> do
+ loopSummaries [ms] (done, summarised)
+ ModuleNodeFixed mod ml -> do
+ done' <- loopFixedModule mod ml done
+ return (done', summarised)
+
+ -- NB: loopFixedModule does not take a downsweep cache, because if you
+ -- ever reach a Fixed node, everything under that also must be fixed.
+ loopFixedModule :: ModNodeKeyWithUid -> ModLocation
+ -> M.Map NodeKey ModuleGraphNode
+ -> IO (M.Map NodeKey ModuleGraphNode)
+ loopFixedModule key loc done = do
+ let nk = NodeKey_Module key
+ case M.lookup nk done of
+ Just {} -> return done
+ Nothing -> do
+ -- MP: TODO, we should just read the dependency info from the interface rather than either
+ -- a. Loading the whole thing into the EPS (this might never nececssary and causes lots of things to be permanently loaded into memory)
+ -- b. Loading the whole interface into a buffer before discarding it. (wasted allocation and deserialisation)
+ read_result <-
+ -- 1. Check if the interface is already loaded into the EPS by some other
+ -- part of the compiler.
+ lookupIfaceByModuleHsc hsc_env (mnkToModule key) >>= \case
+ Just iface -> return (M.Succeeded iface)
+ Nothing -> readIface (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule key) (ml_hi_file loc)
+ case read_result of
+ M.Succeeded iface -> do
+ -- Computer information about this node
+ let node_deps = ifaceDeps (mi_deps iface)
+ edges = map (either NodeKey_Module NodeKey_ExternalUnit) node_deps
+ node = ModuleNode edges (ModuleNodeFixed key loc)
+ foldM (loopFixedNodeKey (mnkUnitId key)) (M.insert nk node done) node_deps
+ -- Ignore any failure, we might try to read a .hi-boot file for
+ -- example, even if there is not one.
+ M.Failed {} ->
+ return done
+
+ loopFixedNodeKey :: UnitId -> M.Map NodeKey ModuleGraphNode -> Either ModNodeKeyWithUid UnitId -> IO (M.Map NodeKey ModuleGraphNode)
+ loopFixedNodeKey _ done (Left key) = do
+ loopFixedImports [key] done
+ loopFixedNodeKey home_uid done (Right uid) = do
+ -- Set active unit so that looking loopUnit finds the correct
+ -- -package flags in the unit state.
+ let hsc_env' = hscSetActiveUnitId home_uid hsc_env
+ return $ loopUnit hsc_env' done [uid]
+
+
+ ifaceDeps :: Dependencies -> [Either ModNodeKeyWithUid UnitId]
+ ifaceDeps deps =
+ [ Left (ModNodeKeyWithUid dep uid)
+ | (uid, dep) <- Set.toList (dep_direct_mods deps)
+ ] ++
+ [ Right uid
+ | uid <- Set.toList (dep_direct_pkgs deps)
+ ]
+
+ -- Like loopImports, but we already know exactly which module we are looking for.
+ loopFixedImports :: [ModNodeKeyWithUid]
+ -> M.Map NodeKey ModuleGraphNode
+ -> IO (M.Map NodeKey ModuleGraphNode)
+ loopFixedImports [] done = pure done
+ loopFixedImports (key:keys) done = do
+ let nk = NodeKey_Module key
+ case M.lookup nk done of
+ Just {} -> loopFixedImports keys done
+ Nothing -> do
+ read_result <- findExactModule hsc_env (mnkToInstalledModule key) (mnkIsBoot key)
+ case read_result of
+ InstalledFound loc -> do
+ done' <- loopFixedModule key loc done
+ loopFixedImports keys done'
+ _otherwise ->
+ -- If the finder fails, just keep going, there will be another
+ -- error later.
+ loopFixedImports keys done
+
+ downsweepSummarise :: HscEnv
+ -> HomeUnit
+ -> M.Map (UnitId, FilePath) ModSummary
+ -> IsBootInterface
+ -> Located ModuleName
+ -> PkgQual
+ -> Maybe (StringBuffer, UTCTime)
+ -> [ModuleName]
+ -> IO SummariseResult
+ downsweepSummarise hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg maybe_buf excl_mods =
+ case mode of
+ DownsweepUseCompile -> summariseModule hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg maybe_buf excl_mods
+ DownsweepUseFixed -> summariseModuleInterface hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods
+
-- This loops over each import in each summary. It is mutually recursive with loopSummaries if we discover
-- a new module by doing this.
@@ -268,7 +486,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
| Just summs <- M.lookup cache_key summarised
= case summs of
[Right ms] -> do
- let nk = NodeKey_Module (msKey ms)
+ let nk = NodeKey_Module (mnKey ms)
(rest, summarised', done') <- loopImports ss done summarised
return (nk: rest, summarised', done')
[Left _err] ->
@@ -277,7 +495,7 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
loopImports ss done summarised
| otherwise
= do
- mb_s <- summariseModule hsc_env home_unit old_summaries
+ mb_s <- downsweepSummarise hsc_env home_unit old_summaries
is_boot wanted_mod mb_pkg
Nothing excl_mods
case mb_s of
@@ -295,11 +513,11 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
FoundHomeWithError (_uid, e) -> loopImports ss done (Map.insert cache_key [(Left e)] summarised)
FoundHome s -> do
(done', summarised') <-
- loopSummaries [s] (done, Map.insert cache_key [Right s] summarised)
+ loopModuleNodeInfo s (done, Map.insert cache_key [Right s] summarised)
(other_deps, final_done, final_summarised) <- loopImports ss done' summarised'
-- MP: This assumes that we can only instantiate non home units, which is probably fair enough for now.
- return (NodeKey_Module (msKey s) : other_deps, final_done, final_summarised)
+ return (NodeKey_Module (mnKey s) : other_deps, final_done, final_summarised)
where
cache_key = (home_uid, mb_pkg, unLoc <$> gwib)
home_unit = ue_unitHomeUnit home_uid (hsc_unit_env hsc_env)
@@ -316,17 +534,17 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
Just us -> loopUnit lcl_hsc_env (loopUnit lcl_hsc_env (Map.insert nk (UnitNode us u) cache) us) uxs
Nothing -> pprPanic "loopUnit" (text "Malformed package database, missing " <+> ppr u)
-multiRootsErr :: [ModSummary] -> IO ()
+multiRootsErr :: [ModuleNodeInfo] -> IO ()
multiRootsErr [] = panic "multiRootsErr"
multiRootsErr summs@(summ1:_)
= throwOneError $ fmap GhcDriverMessage $
mkPlainErrorMsgEnvelope noSrcSpan $ DriverDuplicatedModuleDeclaration mod files
where
- mod = ms_mod summ1
- files = map (expectJust . ml_hs_file . ms_location) summs
+ mod = moduleNodeInfoModule summ1
+ files = mapMaybe (ml_hs_file . moduleNodeInfoLocation) summs
-moduleNotFoundErr :: ModuleName -> DriverMessages
-moduleNotFoundErr mod = singleMessage $ mkPlainErrorMsgEnvelope noSrcSpan (DriverModuleNotFound mod)
+moduleNotFoundErr :: UnitId -> ModuleName -> DriverMessages
+moduleNotFoundErr uid mod = singleMessage $ mkPlainErrorMsgEnvelope noSrcSpan (DriverModuleNotFound uid mod)
-- | Collect the instantiations of dependencies to create 'InstantiationNode' work graph nodes.
-- These are used to represent the type checking that is done after
@@ -380,18 +598,17 @@ getRootSummary ::
M.Map (UnitId, FilePath) ModSummary ->
HscEnv ->
Target ->
- IO (Either (UnitId, DriverMessages) ModSummary)
+ IO (Either DriverMessages ModSummary)
getRootSummary excl_mods old_summary_map hsc_env target
| TargetFile file mb_phase <- targetId
= do
let offset_file = augmentByWorkingDirectory dflags file
exists <- liftIO $ doesFileExist offset_file
if exists || isJust maybe_buf
- then first (uid,) <$>
- summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
+ then summariseFile hsc_env home_unit old_summary_map offset_file mb_phase
maybe_buf
else
- return $ Left $ (uid,) $ singleMessage $
+ return $ Left $ singleMessage $
mkPlainErrorMsgEnvelope noSrcSpan (DriverFileNotFound offset_file)
| TargetModule modl <- targetId
= do
@@ -399,9 +616,9 @@ getRootSummary excl_mods old_summary_map hsc_env target
(L rootLoc modl) (ThisPkg (homeUnitId home_unit))
maybe_buf excl_mods
pure case maybe_summary of
- FoundHome s -> Right s
- FoundHomeWithError err -> Left err
- _ -> Left (uid, moduleNotFoundErr modl)
+ FoundHome (ModuleNodeCompile s) -> Right s
+ FoundHomeWithError err -> Left (snd err)
+ _ -> Left (moduleNotFoundErr uid modl)
where
Target {targetId, targetContents = maybe_buf, targetUnitId = uid} = target
home_unit = ue_unitHomeUnit uid (hsc_unit_env hsc_env)
@@ -426,8 +643,8 @@ rootSummariesParallel ::
HscEnv ->
(GhcMessage -> AnyGhcDiagnostic) ->
Maybe Messager ->
- (HscEnv -> Target -> IO (Either (UnitId, DriverMessages) ModSummary)) ->
- IO ([(UnitId, DriverMessages)], [ModSummary])
+ (HscEnv -> Target -> IO (Either DriverMessages ModSummary)) ->
+ IO ([DriverMessages], [ModSummary])
rootSummariesParallel n_jobs hsc_env diag_wrapper msg get_summary = do
(actions, get_results) <- unzip <$> mapM action_and_result (zip [1..] bundles)
runPipelines n_jobs hsc_env diag_wrapper msg actions
@@ -732,10 +949,10 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = do
-- | Populate the Downsweep cache with the root modules.
mkRootMap
- :: [ModSummary]
+ :: [ModuleNodeInfo]
-> DownsweepCache
mkRootMap summaries = Map.fromListWith (flip (++))
- [ ((ms_unitid s, NoPkgQual, ms_mnwib s), [Right s]) | s <- summaries ]
+ [ ((moduleNodeInfoUnitId s, NoPkgQual, moduleNodeInfoMnwib s), [Right s]) | s <- summaries ]
-----------------------------------------------------------------------------
-- Summarising modules
@@ -863,26 +1080,64 @@ checkSummaryHash
data SummariseResult =
FoundInstantiation InstantiatedUnit
| FoundHomeWithError (UnitId, DriverMessages)
- | FoundHome ModSummary
+ | FoundHome ModuleNodeInfo
| External UnitId
| NotThere
+-- | summariseModule finds the location of the source file for the given module.
+-- This version always returns a ModuleNodeCompile node, it is useful for
+-- --make mode.
+summariseModule :: HscEnv
+ -> HomeUnit
+ -> M.Map (UnitId, FilePath) ModSummary
+ -> IsBootInterface
+ -> Located ModuleName
+ -> PkgQual
+ -> Maybe (StringBuffer, UTCTime)
+ -> [ModuleName]
+ -> IO SummariseResult
+summariseModule hsc_env home_unit old_summaries is_boot wanted_mod mb_pkg maybe_buf excl_mods =
+ summariseModuleDispatch k hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods
+ where
+ k = summariseModuleWithSource home_unit old_summaries is_boot maybe_buf
+
+
+-- | Like summariseModule but for interface files that we don't want to compile.
+-- This version always returns a ModuleNodeFixed node.
+summariseModuleInterface :: HscEnv
+ -> HomeUnit
+ -> IsBootInterface
+ -> Located ModuleName
+ -> PkgQual
+ -> [ModuleName]
+ -> IO SummariseResult
+summariseModuleInterface hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods =
+ summariseModuleDispatch k hsc_env home_unit is_boot wanted_mod mb_pkg excl_mods
+ where
+ k _hsc_env loc mod = do
+ -- The finder will return a path to the .hi-boot even if it doesn't actually
+ -- exist. So check if it exists first before concluding it's there.
+ does_exist <- doesFileExist (ml_hi_file loc)
+ if does_exist
+ then let key = moduleToMnk mod is_boot
+ in return $ FoundHome (ModuleNodeFixed key loc)
+ else return NotThere
+
+
+
-- Summarise a module, and pick up source and timestamp.
-summariseModule
- :: HscEnv
+summariseModuleDispatch
+ :: (HscEnv -> ModLocation -> Module -> IO SummariseResult) -- ^ Continuation about how to summarise a home module.
+ -> HscEnv
-> HomeUnit
- -> M.Map (UnitId, FilePath) ModSummary
- -- ^ Map of old summaries
-> IsBootInterface -- True <=> a {-# SOURCE #-} import
-> Located ModuleName -- Imported module to be summarised
-> PkgQual
- -> Maybe (StringBuffer, UTCTime)
-> [ModuleName] -- Modules to exclude
-> IO SummariseResult
-summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_pkg
- maybe_buf excl_mods
+summariseModuleDispatch k hsc_env' home_unit is_boot (L _ wanted_mod) mb_pkg excl_mods
| wanted_mod `elem` excl_mods
= return NotThere
| otherwise = find_it
@@ -890,7 +1145,6 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
-- Temporarily change the currently active home unit so all operations
-- happen relative to it
hsc_env = hscSetActiveHomeUnit home_unit hsc_env'
- dflags = hsc_dflags hsc_env
find_it :: IO SummariseResult
@@ -898,9 +1152,9 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
found <- findImportedModuleWithIsBoot hsc_env wanted_mod is_boot mb_pkg
case found of
Found location mod
- | isJust (ml_hs_file location) ->
+ | moduleUnitId mod `Set.member` hsc_all_home_unit_ids hsc_env ->
-- Home package
- just_found location mod
+ k hsc_env location mod
| VirtUnit iud <- moduleUnit mod
, not (isHomeModule home_unit mod)
-> return $ FoundInstantiation iud
@@ -910,9 +1164,22 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
-- (If it is TRULY not found at all, we'll
-- error when we actually try to compile)
- just_found location mod = do
- -- Adjust location to point to the hs-boot source file,
- -- hi file, object file, when is_boot says so
+
+-- | The continuation to summarise a home module if we want to find the source file
+-- for it and potentially compile it.
+summariseModuleWithSource
+ :: HomeUnit
+ -> M.Map (UnitId, FilePath) ModSummary
+ -- ^ Map of old summaries
+ -> IsBootInterface -- True <=> a {-# SOURCE #-} import
+ -> Maybe (StringBuffer, UTCTime)
+ -> HscEnv
+ -> ModLocation
+ -> Module
+ -> IO SummariseResult
+summariseModuleWithSource home_unit old_summary_map is_boot maybe_buf hsc_env location mod = do
+ -- Adjust location to point to the hs-boot source file,
+ -- hi file, object file, when is_boot says so
let src_fn = expectJust (ml_hs_file location)
-- Check that it exists
@@ -926,8 +1193,10 @@ summariseModule hsc_env' home_unit old_summary_map is_boot (L _ wanted_mod) mb_p
fresult <- new_summary_cache_check location mod src_fn h
return $ case fresult of
Left err -> FoundHomeWithError (moduleUnitId mod, err)
- Right ms -> FoundHome ms
+ Right ms -> FoundHome (ModuleNodeCompile ms)
+ where
+ dflags = hsc_dflags hsc_env
new_summary_cache_check loc mod src_fn h
| Just old_summary <- Map.lookup ((toUnitId (moduleUnit mod), src_fn)) old_summary_map =
@@ -1061,4 +1330,4 @@ getPreprocessedImports hsc_env src_fn mb_phase maybe_buf = do
let rn_imps = fmap (\(pk, lmn@(L _ mn)) -> (rn_pkg_qual mn pk, lmn))
let pi_srcimps = rn_imps pi_srcimps'
let pi_theimps = rn_imps pi_theimps'
- return PreprocessedImports {..}
\ No newline at end of file
+ return PreprocessedImports {..}
=====================================
compiler/GHC/Driver/Env.hs
=====================================
@@ -27,6 +27,7 @@ module GHC.Driver.Env
, discardIC
, lookupType
, lookupIfaceByModule
+ , lookupIfaceByModuleHsc
, mainModIs
, hugRulesBelow
@@ -249,6 +250,11 @@ hugInstancesBelow hsc_env uid mnwib = do
--
-- Note: Don't expose this function. This is a footgun if exposed!
hugSomeThingsBelowUs :: (HomeModInfo -> [a]) -> Bool -> HscEnv -> UnitId -> ModuleNameWithIsBoot -> IO [[a]]
+-- An explicit check to see if we are in one-shot mode to avoid poking the ModuleGraph thunk
+-- These things are currently stored in the EPS for home packages. (See #25795 for
+-- progress in removing these kind of checks)
+-- See Note [Downsweep and the ModuleGraph]
+hugSomeThingsBelowUs _ _ hsc_env _ _ | isOneShot (ghcMode (hsc_dflags hsc_env)) = return []
hugSomeThingsBelowUs extract include_hi_boot hsc_env uid mn
= let hug = hsc_HUG hsc_env
mg = hsc_mod_graph hsc_env
@@ -345,6 +351,11 @@ lookupIfaceByModule hug pit mod
-- We could eliminate (b) if we wanted, by making GHC.Prim belong to a package
-- of its own, but it doesn't seem worth the bother.
+lookupIfaceByModuleHsc :: HscEnv -> Module -> IO (Maybe ModIface)
+lookupIfaceByModuleHsc hsc_env mod = do
+ eps <- hscEPS hsc_env
+ lookupIfaceByModule (hsc_HUG hsc_env) (eps_PIT eps) mod
+
mainModIs :: HomeUnitEnv -> Module
mainModIs hue = mkHomeModule (expectJust $ homeUnitEnv_home_unit hue) (mainModuleNameIs (homeUnitEnv_dflags hue))
=====================================
compiler/GHC/Driver/Env/Types.hs
=====================================
@@ -67,6 +67,7 @@ data HscEnv
hsc_mod_graph :: ModuleGraph,
-- ^ The module graph of the current session
+ -- See Note [Downsweep and the ModuleGraph] for when this is constructed.
hsc_IC :: InteractiveContext,
-- ^ The context for evaluating interactive statements
=====================================
compiler/GHC/Driver/Errors/Ppr.hs
=====================================
@@ -155,7 +155,7 @@ instance Diagnostic DriverMessage where
text "module" <+> quotes (ppr mod) <+>
text "is defined in multiple files:" <+>
sep (map text files)
- DriverModuleNotFound mod
+ DriverModuleNotFound _uid mod
-> mkSimpleDecorated (text "module" <+> quotes (ppr mod) <+> text "cannot be found locally")
DriverFileModuleNameMismatch actual expected
-> mkSimpleDecorated $
=====================================
compiler/GHC/Driver/Errors/Types.hs
=====================================
@@ -187,7 +187,7 @@ data DriverMessage where
Test cases: None.
-}
- DriverModuleNotFound :: !ModuleName -> DriverMessage
+ DriverModuleNotFound :: !UnitId -> !ModuleName -> DriverMessage
{-| DriverFileModuleNameMismatch occurs if a module 'A' is defined in a file with a different name.
The first field is the name written in the source code; the second argument is the name extracted
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -118,6 +118,7 @@ import GHC.Driver.Backend
import GHC.Driver.Env
import GHC.Driver.Env.KnotVars
import GHC.Driver.Errors
+import GHC.Driver.Messager
import GHC.Driver.Errors.Types
import GHC.Driver.CodeOutput
import GHC.Driver.Config.Cmm.Parser (initCmmParserConfig)
@@ -220,7 +221,6 @@ import GHC.Cmm.UniqueRenamer
import GHC.Unit
import GHC.Unit.Env
import GHC.Unit.Finder
-import GHC.Unit.External
import GHC.Unit.Module.ModDetails
import GHC.Unit.Module.ModGuts
import GHC.Unit.Module.ModIface
@@ -814,7 +814,6 @@ This is the only thing that isn't caught by the type-system.
-}
-type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModuleGraphNode -> IO ()
-- | Do the recompilation avoidance checks for both one-shot and --make modes
-- This function is the *only* place in the compiler where we decide whether to
@@ -1476,46 +1475,6 @@ genModDetails hsc_env old_iface
dumpIfaceStats hsc_env
return new_details
---------------------------------------------------------------
--- Progress displayers.
---------------------------------------------------------------
-
-oneShotMsg :: Logger -> RecompileRequired -> IO ()
-oneShotMsg logger recomp =
- case recomp of
- UpToDate -> compilationProgressMsg logger $ text "compilation IS NOT required"
- NeedsRecompile _ -> return ()
-
-batchMsg :: Messager
-batchMsg = batchMsgWith (\_ _ _ _ -> empty)
-batchMultiMsg :: Messager
-batchMultiMsg = batchMsgWith (\_ _ _ node -> brackets (ppr (mgNodeUnitId node)))
-
-batchMsgWith :: (HscEnv -> (Int, Int) -> RecompileRequired -> ModuleGraphNode -> SDoc) -> Messager
-batchMsgWith extra hsc_env_start mod_index recomp node =
- case recomp of
- UpToDate
- | logVerbAtLeast logger 2 -> showMsg (text "Skipping") empty
- | otherwise -> return ()
- NeedsRecompile reason0 -> showMsg (text herald) $ case reason0 of
- MustCompile -> empty
- (RecompBecause reason) -> text " [" <> pprWithUnitState state (ppr reason) <> text "]"
- where
- herald = case node of
- LinkNode {} -> "Linking"
- InstantiationNode {} -> "Instantiating"
- ModuleNode {} -> "Compiling"
- UnitNode {} -> "Loading"
- hsc_env = hscSetActiveUnitId (mgNodeUnitId node) hsc_env_start
- dflags = hsc_dflags hsc_env
- logger = hsc_logger hsc_env
- state = hsc_units hsc_env
- showMsg msg reason =
- compilationProgressMsg logger $
- (showModuleIndex mod_index <>
- msg <+> showModMsg dflags (recompileRequired recomp) node)
- <> extra hsc_env mod_index recomp node
- <> reason
--------------------------------------------------------------
-- Safe Haskell
@@ -1803,10 +1762,7 @@ hscCheckSafe' m l = do
lookup' :: Module -> Hsc (Maybe ModIface)
lookup' m = do
hsc_env <- getHscEnv
- hsc_eps <- liftIO $ hscEPS hsc_env
- let pkgIfaceT = eps_PIT hsc_eps
- hug = hsc_HUG hsc_env
- iface <- liftIO $ lookupIfaceByModule hug pkgIfaceT m
+ iface <- liftIO $ lookupIfaceByModuleHsc hsc_env m
-- the 'lookupIfaceByModule' method will always fail when calling from GHCi
-- as the compiler hasn't filled in the various module tables
-- so we need to call 'getModuleInterface' to load from disk
@@ -2954,18 +2910,6 @@ dumpIfaceStats hsc_env = do
logDumpMsg logger "Interface statistics" (ifaceStats eps)
-{- **********************************************************************
-%* *
- Progress Messages: Module i of n
-%* *
-%********************************************************************* -}
-
-showModuleIndex :: (Int, Int) -> SDoc
-showModuleIndex (i,n) = text "[" <> pad <> int i <> text " of " <> int n <> text "] "
- where
- -- compute the length of x > 0 in base 10
- len x = ceiling (logBase 10 (fromIntegral x+1) :: Float)
- pad = text (replicate (len n - len i) ' ') -- TODO: use GHC.Utils.Ppr.RStr
writeInterfaceOnlyMode :: DynFlags -> Bool
writeInterfaceOnlyMode dflags =
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -41,6 +41,7 @@ module GHC.Driver.Make (
-- * Re-exports from Downsweep
checkHomeUnitsClosed,
summariseModule,
+ summariseModuleInterface,
SummariseResult(..),
summariseFile,
@@ -648,7 +649,7 @@ load' mhmi_cache how_much diag_wrapper mHscMessage mod_graph = do
| otherwise = do
throwOneError $ mkPlainErrorMsgEnvelope noSrcSpan
$ GhcDriverMessage
- $ DriverModuleNotFound (moduleName m)
+ $ DriverModuleNotFound (moduleUnit m) (moduleName m)
checkHowMuch how_much $ do
@@ -1667,7 +1668,7 @@ executeCompileNode k n !old_hmi hug mrehydrate_mods mni = do
executeCompileNodeFixed hsc_env MakeEnv{diag_wrapper, env_messager} mod loc =
wrapAction diag_wrapper hsc_env $ do
forM_ env_messager $ \hscMessage -> hscMessage hsc_env (k, n) UpToDate (ModuleNode [] (ModuleNodeFixed mod loc))
- read_result <- readIface (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule mod) (ml_hi_file loc)
+ read_result <- readIface (hsc_logger hsc_env) (hsc_dflags hsc_env) (hsc_NC hsc_env) (mnkToModule mod) (ml_hi_file loc)
case read_result of
M.Failed interface_err ->
let mn = mnkModuleName mod
=====================================
compiler/GHC/Driver/MakeAction.hs
=====================================
@@ -25,7 +25,7 @@ import GHC.Driver.DynFlags
import GHC.Driver.Monad
import GHC.Driver.Env
import GHC.Driver.Errors.Types
-import GHC.Driver.Main
+import GHC.Driver.Messager
import GHC.Driver.MakeSem
import GHC.Utils.Logger
=====================================
compiler/GHC/Driver/Messager.hs
=====================================
@@ -0,0 +1,66 @@
+module GHC.Driver.Messager (Messager, oneShotMsg, batchMsg, batchMultiMsg, showModuleIndex) where
+
+import GHC.Prelude
+import GHC.Driver.Env
+import GHC.Unit.Module.Graph
+import GHC.Iface.Recomp
+import GHC.Utils.Logger
+import GHC.Utils.Outputable
+import GHC.Utils.Error
+import GHC.Unit.State
+
+type Messager = HscEnv -> (Int,Int) -> RecompileRequired -> ModuleGraphNode -> IO ()
+
+--------------------------------------------------------------
+-- Progress displayers.
+--------------------------------------------------------------
+
+oneShotMsg :: Logger -> RecompileRequired -> IO ()
+oneShotMsg logger recomp =
+ case recomp of
+ UpToDate -> compilationProgressMsg logger $ text "compilation IS NOT required"
+ NeedsRecompile _ -> return ()
+
+batchMsg :: Messager
+batchMsg = batchMsgWith (\_ _ _ _ -> empty)
+batchMultiMsg :: Messager
+batchMultiMsg = batchMsgWith (\_ _ _ node -> brackets (ppr (mgNodeUnitId node)))
+
+batchMsgWith :: (HscEnv -> (Int, Int) -> RecompileRequired -> ModuleGraphNode -> SDoc) -> Messager
+batchMsgWith extra hsc_env_start mod_index recomp node =
+ case recomp of
+ UpToDate
+ | logVerbAtLeast logger 2 -> showMsg (text "Skipping") empty
+ | otherwise -> return ()
+ NeedsRecompile reason0 -> showMsg (text herald) $ case reason0 of
+ MustCompile -> empty
+ (RecompBecause reason) -> text " [" <> pprWithUnitState state (ppr reason) <> text "]"
+ where
+ herald = case node of
+ LinkNode {} -> "Linking"
+ InstantiationNode {} -> "Instantiating"
+ ModuleNode {} -> "Compiling"
+ UnitNode {} -> "Loading"
+ hsc_env = hscSetActiveUnitId (mgNodeUnitId node) hsc_env_start
+ dflags = hsc_dflags hsc_env
+ logger = hsc_logger hsc_env
+ state = hsc_units hsc_env
+ showMsg msg reason =
+ compilationProgressMsg logger $
+ (showModuleIndex mod_index <>
+ msg <+> showModMsg dflags (recompileRequired recomp) node)
+ <> extra hsc_env mod_index recomp node
+ <> reason
+
+{- **********************************************************************
+%* *
+ Progress Messages: Module i of n
+%* *
+%********************************************************************* -}
+
+showModuleIndex :: (Int, Int) -> SDoc
+showModuleIndex (i,n) = text "[" <> pad <> int i <> text " of " <> int n <> text "] "
+ where
+ -- compute the length of x > 0 in base 10
+ len x = ceiling (logBase 10 (fromIntegral x+1) :: Float)
+ pad = text (replicate (len n - len i) ' ') -- TODO: use GHC.Utils.Ppr.RStr
\ No newline at end of file
=====================================
compiler/GHC/Driver/Pipeline.hs-boot
=====================================
@@ -3,12 +3,22 @@ module GHC.Driver.Pipeline where
import GHC.Driver.Env.Types ( HscEnv )
import GHC.ForeignSrcLang ( ForeignSrcLang )
-import GHC.Prelude (FilePath, IO)
+import GHC.Prelude (FilePath, IO, Maybe, Either)
import GHC.Unit.Module.Location (ModLocation)
import GHC.Driver.Session (DynFlags)
+import GHC.Driver.Phases (Phase)
+import GHC.Driver.Errors.Types (DriverMessages)
+import GHC.Types.Target (InputFileBuffer)
import Language.Haskell.Syntax.Module.Name
-- These are used in GHC.Driver.Pipeline.Execute, but defined in terms of runPipeline
compileForeign :: HscEnv -> ForeignSrcLang -> FilePath -> IO FilePath
compileEmptyStub :: DynFlags -> HscEnv -> FilePath -> ModLocation -> ModuleName -> IO ()
+
+preprocess :: HscEnv
+ -> FilePath
+ -> Maybe InputFileBuffer
+ -> Maybe Phase
+ -> IO (Either DriverMessages (DynFlags, FilePath))
+
=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -33,6 +33,7 @@ import GHC.Unit.Module.ModSummary
import qualified GHC.LanguageExtensions as LangExt
import GHC.Types.SrcLoc
import GHC.Driver.Main
+import GHC.Driver.Downsweep
import GHC.Tc.Types
import GHC.Types.Error
import GHC.Driver.Errors.Types
@@ -760,11 +761,17 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
let msg :: Messager
msg hsc_env _ what _ = oneShotMsg (hsc_logger hsc_env) what
+ -- A lazy module graph thunk, don't force it unless you need it!
+ mg <- downsweepThunk hsc_env mod_summary
+
-- Need to set the knot-tying mutable variable for interface
-- files. See GHC.Tc.Utils.TcGblEnv.tcg_type_env_var.
-- See also Note [hsc_type_env_var hack]
type_env_var <- newIORef emptyNameEnv
- let hsc_env' = hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)]) }
+ let hsc_env' = hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)])
+ , hsc_mod_graph = mg }
+
+
status <- hscRecompStatus (Just msg) hsc_env' mod_summary
Nothing emptyHomeModInfoLinkable (1, 1)
=====================================
compiler/GHC/Iface/Load.hs
=====================================
@@ -25,7 +25,6 @@ module GHC.Iface.Load (
-- IfM functions
loadInterface,
loadSysInterface, loadUserInterface, loadPluginInterface,
- loadExternalGraphBelow,
findAndReadIface, readIface, writeIface,
flagsToIfCompression,
moduleFreeHolesPrecise,
@@ -49,7 +48,6 @@ import {-# SOURCE #-} GHC.IfaceToCore
( tcIfaceDecls, tcIfaceRules, tcIfaceInst, tcIfaceFamInst
, tcIfaceAnnotations, tcIfaceCompleteMatches, tcIfaceDefaults)
-import GHC.Driver.Config.Finder
import GHC.Driver.Env
import GHC.Driver.Errors.Types
import GHC.Driver.DynFlags
@@ -110,7 +108,6 @@ import GHC.Unit.Home
import GHC.Unit.Home.PackageTable
import GHC.Unit.Finder
import GHC.Unit.Env
-import GHC.Unit.Module.External.Graph
import GHC.Data.Maybe
@@ -122,7 +119,6 @@ import GHC.Driver.Env.KnotVars
import {-# source #-} GHC.Driver.Main (loadIfaceByteCode)
import GHC.Iface.Errors.Types
import Data.Function ((&))
-import qualified Data.Set as Set
import GHC.Unit.Module.Graph
import qualified GHC.Unit.Home.Graph as HUG
@@ -413,112 +409,6 @@ loadInterfaceWithException doc mod_name where_from
let ctx = initSDocContext dflags defaultUserStyle
withIfaceErr ctx (loadInterface doc mod_name where_from)
--- | Load the part of the external module graph which is transitively reachable
--- from the given modules.
---
--- This operation is used just before TH splices are run (in 'getLinkDeps').
---
--- A field in the EPS tracks which home modules are already fully loaded, which we use
--- here to avoid trying to load them a second time.
---
--- The function takes a set of keys which are currently in the process of being loaded.
--- This is used to avoid duplicating work by loading keys twice if they appear along multiple
--- paths in the transitive closure. Once the interface and all its dependencies are
--- loaded, the key is added to the "fully loaded" set, so we know that it and it's
--- transitive closure are present in the graph.
---
--- Note that being "in progress" is different from being "fully loaded", consider if there
--- is an exception during `loadExternalGraphBelow`, then an "in progress" item may fail
--- to become fully loaded.
-loadExternalGraphBelow :: (Module -> SDoc) -> Maybe HomeUnit {-^ The current home unit -}
- -> Set.Set ExternalKey -> [Module] -> IfM lcl (Set.Set ExternalKey)
-loadExternalGraphBelow _ Nothing _ _ = panic "loadExternalGraphBelow: No home unit"
-loadExternalGraphBelow msg (Just home_unit) in_progress mods =
- foldM (loadExternalGraphModule msg home_unit) in_progress mods
-
--- | Load the interface for a module, and all its transitive dependencies but
--- only if we haven't fully loaded the module already or are in the process of fully loading it.
-loadExternalGraphModule :: (Module -> SDoc) -> HomeUnit
- -> Set.Set ExternalKey
- -> Module
- -> IfM lcl (Set.Set ExternalKey)
-loadExternalGraphModule msg home_unit in_progress mod
- | homeUnitId home_unit /= moduleUnitId mod = do
- loadExternalPackageBelow in_progress (moduleUnitId mod)
- | otherwise = do
-
- let key = ExternalModuleKey $ ModNodeKeyWithUid (GWIB (moduleName mod) NotBoot) (moduleUnitId mod)
- graph <- eps_module_graph <$> getEps
-
- if (not (isFullyLoadedModule key graph || Set.member key in_progress))
- then actuallyLoadExternalGraphModule msg home_unit in_progress key mod
- else return in_progress
-
--- | Load the interface for a module, and all its transitive dependenices.
-actuallyLoadExternalGraphModule
- :: (Module -> SDoc)
- -> HomeUnit
- -> Set.Set ExternalKey
- -> ExternalKey
- -> Module
- -> IOEnv (Env IfGblEnv lcl) (Set.Set ExternalKey)
-actuallyLoadExternalGraphModule msg home_unit in_progress key mod = do
- dflags <- getDynFlags
- let ctx = initSDocContext dflags defaultUserStyle
- iface <- withIfaceErr ctx $
- loadInterface (msg mod) mod (ImportByUser NotBoot)
-
- let deps = mi_deps iface
- mod_deps = dep_direct_mods deps
- pkg_deps = dep_direct_pkgs deps
-
- -- Do not attempt to load the same key again when traversing
- let in_progress' = Set.insert key in_progress
-
- -- Load all direct dependencies that are in the home package
- cache_mods <- loadExternalGraphBelow msg (Just home_unit) in_progress'
- $ map (\(uid, GWIB mn _) -> mkModule (RealUnit (Definite uid)) mn)
- $ Set.toList mod_deps
-
- -- Load all the package nodes, and packages beneath them.
- cache_pkgs <- foldM loadExternalPackageBelow cache_mods (Set.toList pkg_deps)
-
- registerFullyLoaded key
- return cache_pkgs
-
-registerFullyLoaded :: ExternalKey -> IfM lcl ()
-registerFullyLoaded key = do
- -- Update the external graph with this module being fully loaded.
- logger <- getLogger
- liftIO $ trace_if logger (text "Fully loaded:" <+> ppr key)
- updateEps_ $ \eps ->
- eps{eps_module_graph = setFullyLoadedModule key (eps_module_graph eps)}
-
-loadExternalPackageBelow :: Set.Set ExternalKey -> UnitId -> IfM lcl (Set.Set ExternalKey)
-loadExternalPackageBelow in_progress uid = do
- graph <- eps_module_graph <$> getEps
- us <- hsc_units <$> getTopEnv
- let key = ExternalPackageKey uid
- if not (isFullyLoadedModule key graph || Set.member key in_progress)
- then do
- let in_progress' = Set.insert key in_progress
- case unitDepends <$> lookupUnitId us uid of
- Just dep_uids -> do
- loadPackageIntoEPSGraph uid dep_uids
- final_cache <- foldM loadExternalPackageBelow in_progress' dep_uids
- registerFullyLoaded key
- return final_cache
- Nothing -> pprPanic "loadExternalPackagesBelow: missing" (ppr uid)
- else
- return in_progress
-
-loadPackageIntoEPSGraph :: UnitId -> [UnitId] -> IfM lcl ()
-loadPackageIntoEPSGraph uid dep_uids =
- updateEps_ $ \eps ->
- eps { eps_module_graph =
- extendExternalModuleGraph (NodeExternalPackage uid
- (Set.fromList dep_uids)) (eps_module_graph eps) }
-
------------------
loadInterface :: SDoc -> Module -> WhereFrom
-> IfM lcl (MaybeErr MissingInterfaceError ModIface)
@@ -628,15 +518,6 @@ loadInterface doc_str mod from
; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface)
; purged_hsc_env <- getTopEnv
- ; let direct_deps = map (uncurry (flip ModNodeKeyWithUid)) $ (Set.toList (dep_direct_mods $ mi_deps iface))
- ; let direct_pkg_deps = Set.toList $ dep_direct_pkgs $ mi_deps iface
- ; let !module_graph_key =
- if moduleUnitId mod `elem` hsc_all_home_unit_ids hsc_env
- --- ^ home unit mods in eps can only happen in oneshot mode
- then Just $ NodeHomePackage (miKey iface) (map ExternalModuleKey direct_deps
- ++ map ExternalPackageKey direct_pkg_deps)
- else Nothing
-
; let final_iface = iface
& set_mi_decls (panic "No mi_decls in PIT")
& set_mi_insts (panic "No mi_insts in PIT")
@@ -678,11 +559,6 @@ loadInterface doc_str mod from
eps_iface_bytecode = add_bytecode (eps_iface_bytecode eps),
eps_rule_base = extendRuleBaseList (eps_rule_base eps)
new_eps_rules,
- eps_module_graph =
- let eps_graph' = case module_graph_key of
- Just k -> extendExternalModuleGraph k (eps_module_graph eps)
- Nothing -> eps_module_graph eps
- in eps_graph',
eps_complete_matches
= eps_complete_matches eps ++ new_eps_complete_matches,
eps_inst_env = extendInstEnvList (eps_inst_env eps)
@@ -792,6 +668,9 @@ dontLeakTheHUG thing_inside = do
-- tweak.
old_unit_env = hsc_unit_env hsc_env
keepFor20509
+ -- oneshot mode does not support backpack
+ -- and we want to avoid prodding the hsc_mod_graph thunk
+ | isOneShot (ghcMode (hsc_dflags hsc_env)) = False
| mgHasHoles (hsc_mod_graph hsc_env) = True
| otherwise = False
pruneHomeUnitEnv hme = do
@@ -1012,12 +891,10 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
let profile = targetProfile dflags
unit_state = hsc_units hsc_env
- fc = hsc_FC hsc_env
name_cache = hsc_NC hsc_env
mhome_unit = hsc_home_unit_maybe hsc_env
dflags = hsc_dflags hsc_env
logger = hsc_logger hsc_env
- other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env)
trace_if logger (sep [hsep [text "Reading",
@@ -1036,9 +913,8 @@ findAndReadIface hsc_env doc_str mod wanted_mod hi_boot_file = do
let iface = getGhcPrimIface hsc_env
return (Succeeded (iface, panic "GHC.Prim ModLocation (findAndReadIface)"))
else do
- let fopts = initFinderOpts dflags
-- Look for the file
- mb_found <- liftIO (findExactModule fc fopts other_fopts unit_state mhome_unit mod hi_boot_file)
+ mb_found <- liftIO (findExactModule hsc_env mod hi_boot_file)
case mb_found of
InstalledFound loc -> do
-- See Note [Home module load error]
@@ -1101,7 +977,6 @@ read_file :: Logger -> NameCache -> UnitState -> DynFlags
-> Module -> FilePath
-> IO (MaybeErr ReadInterfaceError (ModIface, FilePath))
read_file logger name_cache unit_state dflags wanted_mod file_path = do
- trace_if logger (text "readIFace" <+> text file_path)
-- Figure out what is recorded in mi_module. If this is
-- a fully definite interface, it'll match exactly, but
@@ -1112,7 +987,7 @@ read_file logger name_cache unit_state dflags wanted_mod file_path = do
(_, Just indef_mod) ->
instModuleToModule unit_state
(uninstantiateInstantiatedModule indef_mod)
- read_result <- readIface dflags name_cache wanted_mod' file_path
+ read_result <- readIface logger dflags name_cache wanted_mod' file_path
case read_result of
Failed err -> return (Failed err)
Succeeded iface -> return (Succeeded (iface, file_path))
@@ -1139,12 +1014,14 @@ flagsToIfCompression dflags
-- Failed err <=> file not found, or unreadable, or illegible
-- Succeeded iface <=> successfully found and parsed
readIface
- :: DynFlags
+ :: Logger
+ -> DynFlags
-> NameCache
-> Module
-> FilePath
-> IO (MaybeErr ReadInterfaceError ModIface)
-readIface dflags name_cache wanted_mod file_path = do
+readIface logger dflags name_cache wanted_mod file_path = do
+ trace_if logger (text "readIFace" <+> text file_path)
let profile = targetProfile dflags
res <- tryMost $ readBinIface profile name_cache CheckHiWay QuietBinIFace file_path
case res of
=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -23,7 +23,6 @@ import GHC.Prelude
import GHC.Data.FastString
import GHC.Driver.Backend
-import GHC.Driver.Config.Finder
import GHC.Driver.Env
import GHC.Driver.DynFlags
import GHC.Driver.Ppr
@@ -303,7 +302,7 @@ check_old_iface hsc_env mod_summary maybe_iface
loadIface read_dflags iface_path = do
let ncu = hsc_NC hsc_env
- read_result <- readIface read_dflags ncu (ms_mod mod_summary) iface_path
+ read_result <- readIface logger read_dflags ncu (ms_mod mod_summary) iface_path
case read_result of
Failed err -> do
let msg = readInterfaceErrorDiagnostic err
@@ -635,7 +634,7 @@ checkDependencies :: HscEnv -> ModSummary -> ModIface -> IfG RecompileRequired
checkDependencies hsc_env summary iface
= do
res_normal <- classify_import (findImportedModule hsc_env) (ms_textual_imps summary ++ ms_srcimps summary)
- res_plugin <- classify_import (\mod _ -> findPluginModule fc fopts units mhome_unit mod) (ms_plugin_imps summary)
+ res_plugin <- classify_import (\mod _ -> findPluginModule hsc_env mod) (ms_plugin_imps summary)
case sequence (res_normal ++ res_plugin) of
Left recomp -> return $ NeedsRecompile recomp
Right es -> do
@@ -657,13 +656,8 @@ checkDependencies hsc_env summary iface
let reason = ModuleChanged mod
in classify reason <$> find_import mod mb_pkg)
imports
- dflags = hsc_dflags hsc_env
- fopts = initFinderOpts dflags
logger = hsc_logger hsc_env
- fc = hsc_FC hsc_env
- mhome_unit = hsc_home_unit_maybe hsc_env
all_home_units = hsc_all_home_unit_ids hsc_env
- units = hsc_units hsc_env
prev_dep_mods = map (second gwib_mod) $ Set.toAscList $ dep_direct_mods (mi_deps iface)
prev_dep_pkgs = Set.toAscList (Set.union (dep_direct_pkgs (mi_deps iface))
(dep_plugin_pkgs (mi_deps iface)))
=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -228,31 +228,6 @@ See Note [Home module build products] for some more information about that.
The only other place where the flag is consulted is when enabling code generation
with `-fno-code`, which does so to anticipate what decision we will make at the
splice point about what we would prefer.
-
-Note [Reachability in One-shot mode vs Make mode]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Why are there two code paths in `get_reachable_nodes`? (ldOneShotMode vs otherwise)
-
-In one-shot mode, the home package modules are loaded into the EPS,
-whereas for --make mode, the home package modules are in the HUG/HPT.
-
-For both of these cases, we cache the calculation of transitive
-dependencies in a 'ModuleGraph'. For the --make case, the relevant
-'ModuleGraph' is in the EPS, the other case uses the 'ModuleGraph'
-for the home modules.
-
-The home modules graph is known statically after downsweep.
-On the contrary, the EPS module graph is only extended when a
-module is loaded into the EPS -- which is done lazily as needed.
-Therefore, for get_link_deps, we need to force the transitive
-closure to be loaded before querying the graph for the reachable
-link dependencies -- done in the call to 'loadExternalGraphBelow'.
-Because we cache the transitive closure, this work is only done once.
-
-After forcing the modules with the call to 'loadExternalGraphBelow' in
-'get_reachable_nodes', the external module graph has all edges needed to
-compute the full transitive closure so we can proceed just like we do in the
-second path with a normal module graph.
-}
dieWith :: LinkDepsOpts -> SrcSpan -> SDoc -> IO a
=====================================
compiler/GHC/Linker/Loader.hs
=====================================
@@ -76,12 +76,10 @@ import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Unit.Env
-import GHC.Unit.Home
import GHC.Unit.Home.ModInfo
import GHC.Unit.External (ExternalPackageState (..))
import GHC.Unit.Module
import GHC.Unit.Module.ModNodeKey
-import GHC.Unit.Module.External.Graph
import GHC.Unit.Module.Graph
import GHC.Unit.Module.ModIface
import GHC.Unit.State as Packages
@@ -119,6 +117,9 @@ import System.Win32.Info (getSystemDirectory)
import GHC.Utils.Exception
import GHC.Unit.Home.Graph (lookupHug, unitEnv_foldWithKey)
+import GHC.Driver.Downsweep
+
+
-- Note [Linkers and loaders]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -615,89 +616,53 @@ initLinkDepsOpts hsc_env = opts
dflags = hsc_dflags hsc_env
ldLoadByteCode mod = do
+ _ <- initIfaceLoad hsc_env $
+ loadInterface (text "get_reachable_nodes" <+> parens (ppr mod))
+ mod ImportBySystem
EPS {eps_iface_bytecode} <- hscEPS hsc_env
sequence (lookupModuleEnv eps_iface_bytecode mod)
--- See Note [Reachability in One-shot mode vs Make mode]
get_reachable_nodes :: HscEnv -> [Module] -> IO ([Module], UniqDSet UnitId)
get_reachable_nodes hsc_env mods
- -- Reachability on 'ExternalModuleGraph' (for one shot mode)
- | isOneShot (ghcMode dflags)
+ -- Fallback case if the ModuleGraph has not been initialised by the user.
+ -- This can happen if is the user is loading plugins or doing something else very
+ -- early in the compiler pipeline.
+ | isEmptyMG (hsc_mod_graph hsc_env)
= do
- initIfaceCheck (text "loader") hsc_env
- $ void $ loadExternalGraphBelow msg (hsc_home_unit_maybe hsc_env) Set.empty mods
- -- Read the EPS only after `loadExternalGraphBelow`
- eps <- hscEPS hsc_env
- let
- emg = eps_module_graph eps
- get_mod_info_eps (ModNodeKeyWithUid gwib uid)
- | uid == homeUnitId (ue_unsafeHomeUnit unit_env)
- = case lookupModuleEnv (eps_PIT eps) (Module (RealUnit $ Definite uid) (gwib_mod gwib)) of
- Just iface -> return $ Just iface
- Nothing -> moduleNotLoaded "(in EPS)" gwib uid
- | otherwise
- = return Nothing
-
- get_mod_key m
- | moduleUnitId m == homeUnitId (ue_unsafeHomeUnit unit_env)
- = ExternalModuleKey (mkModuleNk m)
- | otherwise = ExternalPackageKey (moduleUnitId m)
-
- go get_mod_key emgNodeKey (emgReachableLoopMany emg) (map emgProject) get_mod_info_eps
+ mg <- downsweepInstalledModules hsc_env mods
+ go mg
- -- Reachability on 'ModuleGraph' (for --make mode)
| otherwise
- = go hmgModKey mkNodeKey (mgReachableLoop hmGraph) (catMaybes . map hmgProject) get_mod_info_hug
+ = go (hsc_mod_graph hsc_env)
where
- dflags = hsc_dflags hsc_env
unit_env = hsc_unit_env hsc_env
mkModuleNk m = ModNodeKeyWithUid (GWIB (moduleName m) NotBoot) (moduleUnitId m)
- msg mod =
- text "need to link module" <+> ppr mod <+>
- text "and the modules below it, due to use of Template Haskell"
-
- hmGraph = hsc_mod_graph hsc_env
- hmgModKey m
+ hmgModKey mg m
| let k = NodeKey_Module (mkModuleNk m)
- , mgMember hmGraph k = k
+ , mgMember mg k = k
| otherwise = NodeKey_ExternalUnit (moduleUnitId m)
- hmgProject = \case
- NodeKey_Module with_uid -> Just $ Left with_uid
- NodeKey_ExternalUnit uid -> Just $ Right uid
- _ -> Nothing
-
- emgProject = \case
- ExternalModuleKey with_uid -> Left with_uid
- ExternalPackageKey uid -> Right uid
-
-- The main driver for getting dependencies, which calls the given
-- functions to compute the reachable nodes.
- go :: (Module -> key)
- -> (node -> key)
- -> ([key] -> [node])
- -> ([key] -> [Either ModNodeKeyWithUid UnitId])
- -> (ModNodeKeyWithUid -> IO (Maybe ModIface))
- -> IO ([Module], UniqDSet UnitId)
- go modKey nodeKey manyReachable project get_mod_info
- | let mod_keys = map modKey mods
- = do
- let (all_home_mods, pkgs_s) = partitionEithers $ project $ mod_keys ++ map nodeKey (manyReachable mod_keys)
- ifaces <- mapMaybeM get_mod_info all_home_mods
- let mods_s = map mi_module ifaces
+ go :: ModuleGraph -> IO ([Module], UniqDSet UnitId)
+ go mg = do
+ let mod_keys = map (hmgModKey mg) mods
+ all_reachable = mod_keys ++ map mkNodeKey (mgReachableLoop mg mod_keys)
+ (mods_s, pkgs_s) <- partitionEithers <$> mapMaybeM get_mod_info all_reachable
return (mods_s, mkUniqDSet pkgs_s)
- get_mod_info_hug (ModNodeKeyWithUid gwib uid) =
+ get_mod_info :: NodeKey -> IO (Maybe (Either Module UnitId))
+ get_mod_info (NodeKey_Module m@(ModNodeKeyWithUid gwib uid)) =
lookupHug (ue_home_unit_graph unit_env) uid (gwib_mod gwib) >>= \case
- Just hmi -> return $ Just (hm_iface hmi)
- Nothing -> moduleNotLoaded "(in HUG)" gwib uid
+ Just hmi -> return $ Just (Left (mi_module (hm_iface hmi)))
+ Nothing -> return (Just (Left (mnkToModule m)))
+ get_mod_info (NodeKey_ExternalUnit uid) = return (Just (Right uid))
+ get_mod_info _ = return Nothing
- moduleNotLoaded m gwib uid = throwGhcExceptionIO $ ProgramError $ showSDoc dflags $
- text "getLinkDeps: Home module not loaded" <+> text m <+> ppr (gwib_mod gwib) <+> ppr uid
{- **********************************************************************
=====================================
compiler/GHC/Runtime/Loader.hs
=====================================
@@ -56,7 +56,6 @@ import GHC.Types.Name.Reader
import GHC.Types.Unique.DFM
import GHC.Unit.Finder ( findPluginModule, FindResult(..) )
-import GHC.Driver.Config.Finder ( initFinderOpts )
import GHC.Driver.Config.Diagnostic ( initIfaceMessageOpts )
import GHC.Unit.Module ( Module, ModuleName, thisGhcUnit, GenModule(moduleUnit), IsBootInterface(NotBoot) )
import GHC.Unit.Module.ModIface
@@ -343,13 +342,8 @@ lookupRdrNameInModuleForPlugins :: HasDebugCallStack
-> IO (Maybe (Name, ModIface))
lookupRdrNameInModuleForPlugins hsc_env mod_name rdr_name = do
let dflags = hsc_dflags hsc_env
- let fopts = initFinderOpts dflags
- let fc = hsc_FC hsc_env
- let unit_env = hsc_unit_env hsc_env
- let unit_state = ue_homeUnitState unit_env
- let mhome_unit = hsc_home_unit_maybe hsc_env
-- First find the unit the module resides in by searching exposed units and home modules
- found_module <- findPluginModule fc fopts unit_state mhome_unit mod_name
+ found_module <- findPluginModule hsc_env mod_name
case found_module of
Found _ mod -> do
-- Find the exports of the module
=====================================
compiler/GHC/Unit/External.hs
=====================================
@@ -33,7 +33,6 @@ import GHC.Types.TypeEnv
import GHC.Types.Unique.DSet
import GHC.Linker.Types (Linkable)
-import GHC.Unit.Module.External.Graph
import Data.IORef
@@ -72,7 +71,6 @@ initExternalPackageState = EPS
, eps_PIT = emptyPackageIfaceTable
, eps_free_holes = emptyInstalledModuleEnv
, eps_PTE = emptyTypeEnv
- , eps_module_graph = emptyExternalModuleGraph
, eps_iface_bytecode = emptyModuleEnv
, eps_inst_env = emptyInstEnv
, eps_fam_inst_env = emptyFamInstEnv
@@ -141,8 +139,6 @@ data ExternalPackageState
-- for every import, so cache it here. When the PIT
-- gets filled in we can drop these entries.
- eps_module_graph :: ExternalModuleGraph,
-
eps_PTE :: !PackageTypeEnv,
-- ^ Result of typechecking all the external package
-- interface files we have sucked in. The domain of
=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -66,7 +66,6 @@ import Control.Monad
import Data.Time
import qualified Data.Map as M
import GHC.Driver.Env
- ( hsc_home_unit_maybe, HscEnv(hsc_FC, hsc_dflags, hsc_unit_env) )
import GHC.Driver.Config.Finder
import qualified Data.Set as Set
import Data.List.NonEmpty ( NonEmpty (..) )
@@ -224,21 +223,26 @@ findImportedModuleNoHsc fc fopts ue mhome_unit mod_name mb_pkg =
-- plugin. This consults the same set of exposed packages as
-- 'findImportedModule', unless @-hide-all-plugin-packages@ or
-- @-plugin-package@ are specified.
-findPluginModule :: FinderCache -> FinderOpts -> UnitState -> Maybe HomeUnit -> ModuleName -> IO FindResult
-findPluginModule fc fopts units (Just home_unit) mod_name =
+findPluginModuleNoHsc :: FinderCache -> FinderOpts -> UnitState -> Maybe HomeUnit -> ModuleName -> IO FindResult
+findPluginModuleNoHsc fc fopts units (Just home_unit) mod_name =
findHomeModule fc fopts home_unit mod_name
`orIfNotFound`
findExposedPluginPackageModule fc fopts units mod_name
-findPluginModule fc fopts units Nothing mod_name =
+findPluginModuleNoHsc fc fopts units Nothing mod_name =
findExposedPluginPackageModule fc fopts units mod_name
--- | Locate a specific 'Module'. The purpose of this function is to
--- create a 'ModLocation' for a given 'Module', that is to find out
--- where the files associated with this module live. It is used when
--- reading the interface for a module mentioned by another interface,
--- for example (a "system import").
-findExactModule :: FinderCache -> FinderOpts -> UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
-findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
+findPluginModule :: HscEnv -> ModuleName -> IO FindResult
+findPluginModule hsc_env mod_name = do
+ let fc = hsc_FC hsc_env
+ let units = hsc_units hsc_env
+ let mhome_unit = hsc_home_unit_maybe hsc_env
+ findPluginModuleNoHsc fc (initFinderOpts (hsc_dflags hsc_env)) units mhome_unit mod_name
+
+
+-- | A version of findExactModule which takes the exact parts of the HscEnv it needs
+-- directly.
+findExactModuleNoHsc :: FinderCache -> FinderOpts -> UnitEnvGraph FinderOpts -> UnitState -> Maybe HomeUnit -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
+findExactModuleNoHsc fc fopts other_fopts unit_state mhome_unit mod is_boot = do
res <- case mhome_unit of
Just home_unit
| isHomeInstalledModule home_unit mod
@@ -251,6 +255,21 @@ findExactModule fc fopts other_fopts unit_state mhome_unit mod is_boot = do
_ -> return res
+-- | Locate a specific 'Module'. The purpose of this function is to
+-- create a 'ModLocation' for a given 'Module', that is to find out
+-- where the files associated with this module live. It is used when
+-- reading the interface for a module mentioned by another interface,
+-- for example (a "system import").
+findExactModule :: HscEnv -> InstalledModule -> IsBootInterface -> IO InstalledFindResult
+findExactModule hsc_env mod is_boot = do
+ let dflags = hsc_dflags hsc_env
+ let fc = hsc_FC hsc_env
+ let unit_state = hsc_units hsc_env
+ let home_unit = hsc_home_unit_maybe hsc_env
+ let other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env)
+ findExactModuleNoHsc fc (initFinderOpts dflags) other_fopts unit_state home_unit mod is_boot
+
+
-- -----------------------------------------------------------------------------
-- Helpers
=====================================
compiler/GHC/Unit/Module/External/Graph.hs deleted
=====================================
@@ -1,244 +0,0 @@
-{-# LANGUAGE LambdaCase #-}
-{-# LANGUAGE RecordWildCards #-}
-
--- | Like @'GHC.Unit.Module.Graph'@ but for the @'ExternalModuleGraph'@ which is
--- stored in the EPS.
-module GHC.Unit.Module.External.Graph
- ( -- * External Module Graph
- --
- -- | A module graph for the EPS.
- ExternalModuleGraph, ExternalGraphNode(..)
- , ExternalKey(..), emptyExternalModuleGraph
- , emgNodeKey, emgNodeDeps, emgLookupKey
-
- -- * Extending
- --
- -- | The @'ExternalModuleGraph'@ is a structure which is incrementally
- -- updated as the 'ExternalPackageState' (EPS) is updated (when an iface is
- -- loaded, in 'loadInterface').
- --
- -- Therefore, there is an operation for extending the 'ExternalModuleGraph',
- -- unlike @'GHC.Unit.Module.Graph.ModuleGraph'@, which is constructed once
- -- during downsweep and never altered (since all of the home units
- -- dependencies are fully known then).
- , extendExternalModuleGraph
-
- -- * Loading
- --
- -- | As mentioned in the top-level haddocks for the
- -- 'extendExternalModuleGraph', the external module graph is incrementally
- -- updated as interfaces are loaded. This module graph keeps an additional
- -- cache registering which modules have already been fully loaded.
- --
- -- This cache is necessary to quickly check when a full-transitive-closure
- -- reachability query would be valid for some module.
- --
- -- Such a query may be invalid if ran on a module in the
- -- 'ExternalModuleGraph' whose dependencies have /not yet/ been fully loaded
- -- into the EPS.
- -- (Recall that interfaces are lazily loaded, and the 'ExternalModuleGraph'
- -- is only incrementally updated).
- --
- -- To guarantee the full transitive closure of a given module is completely
- -- loaded into the EPS (i.e. all interfaces of the modules below this one
- -- are also loaded), see @'loadExternalGraphBelow'@ in
- -- 'GHC.Iface.Load'.
- , isFullyLoadedModule
- , setFullyLoadedModule
-
- -- * Reachability
- --
- -- | Fast reachability queries on the external module graph. Similar to
- -- reachability queries on 'GHC.Unit.Module.Graph'.
- , emgReachableLoop
- , emgReachableLoopMany
- ) where
-
-import GHC.Prelude
-import GHC.Unit.Module.Graph
-import GHC.Data.Graph.Directed.Reachability
-import GHC.Data.Graph.Directed
-import qualified Data.Map as M
-import qualified Data.Set as S
-import Data.Bifunctor (first, bimap)
-import Data.Maybe
-import GHC.Utils.Outputable
-import GHC.Unit.Types (UnitId, GenWithIsBoot(..), IsBootInterface(..), mkModule)
-import GHC.Utils.Misc
-
-
---------------------------------------------------------------------------------
--- * Main
---------------------------------------------------------------------------------
-
-data ExternalModuleGraph = ExternalModuleGraph
- { external_nodes :: [ExternalGraphNode]
- -- This transitive dependency query does not contain hs-boot nodes.
- , external_trans :: (ReachabilityIndex ExternalNode, ExternalKey -> Maybe ExternalNode)
- , external_fully_loaded :: !(S.Set ExternalKey) }
-
-type ExternalNode = Node Int ExternalGraphNode
-
-data ExternalGraphNode
- -- | A node for a home package module that is inserted in the EPS.
- --
- -- INVARIANT: This type of node can only ever exist if compiling in one-shot
- -- mode. In --make mode, it is imperative that the EPS doesn't have any home
- -- package modules ever.
- = NodeHomePackage
- { externalNodeKey :: ModNodeKeyWithUid
- , externalNodeDeps :: [ExternalKey] }
- -- | A node for packages with at least one module loaded in the EPS.
- --
- -- Edge from A to NodeExternalPackage p when A has p as a direct package
- -- dependency.
- | NodeExternalPackage
- { externalPkgKey :: UnitId
- , externalPkgDeps :: S.Set UnitId
- }
-
-data ExternalKey
- = ExternalModuleKey ModNodeKeyWithUid
- | ExternalPackageKey UnitId
- deriving (Eq, Ord)
-
-emptyExternalModuleGraph :: ExternalModuleGraph
-emptyExternalModuleGraph = ExternalModuleGraph [] (graphReachability emptyGraph, const Nothing) S.empty
-
--- | Get the dependencies of an 'ExternalNode'
-emgNodeDeps :: Bool -> ExternalGraphNode -> [ExternalKey]
-emgNodeDeps drop_hs_boot_nodes = \case
- NodeHomePackage _ dps -> map drop_hs_boot dps
- NodeExternalPackage _ dps -> map ExternalPackageKey $ S.toList dps
- where
- -- Drop hs-boot nodes by using HsSrcFile as the key
- hs_boot_key | drop_hs_boot_nodes = NotBoot -- is regular mod or signature
- | otherwise = IsBoot
-
- drop_hs_boot (ExternalModuleKey (ModNodeKeyWithUid (GWIB mn IsBoot) uid)) = (ExternalModuleKey (ModNodeKeyWithUid (GWIB mn hs_boot_key) uid))
- drop_hs_boot x = x
-
--- | The graph key for a given node
-emgNodeKey :: ExternalGraphNode -> ExternalKey
-emgNodeKey (NodeHomePackage k _) = ExternalModuleKey k
-emgNodeKey (NodeExternalPackage k _) = ExternalPackageKey k
-
--- | Lookup a key in the EMG.
-emgLookupKey :: ExternalKey -> ExternalModuleGraph -> Maybe ExternalGraphNode
-emgLookupKey k emg = node_payload <$> (snd (external_trans emg)) k
-
---------------------------------------------------------------------------------
--- * Extending
---------------------------------------------------------------------------------
-
-extendExternalModuleGraph :: ExternalGraphNode -> ExternalModuleGraph -> ExternalModuleGraph
-extendExternalModuleGraph node ExternalModuleGraph{..} =
- ExternalModuleGraph
- { external_fully_loaded = external_fully_loaded
- , external_nodes = node : external_nodes
- , external_trans = first cyclicGraphReachability $
- externalGraphNodes True (node : external_nodes)
- }
-
---------------------------------------------------------------------------------
--- * Loading
---------------------------------------------------------------------------------
-
-isFullyLoadedModule :: ExternalKey -> ExternalModuleGraph -> Bool
-isFullyLoadedModule key graph = S.member key (external_fully_loaded graph)
-
-setFullyLoadedModule :: ExternalKey -> ExternalModuleGraph -> ExternalModuleGraph
-setFullyLoadedModule key graph = graph { external_fully_loaded = S.insert key (external_fully_loaded graph)}
-
---------------------------------------------------------------------------------
--- * Reachability
---------------------------------------------------------------------------------
-
--- | Return all nodes reachable from the given key, also known as its full
--- transitive closure.
---
--- @Nothing@ if the key couldn't be found in the graph.
-emgReachableLoop :: ExternalModuleGraph -> ExternalKey -> Maybe [ExternalGraphNode]
-emgReachableLoop mg nk = map node_payload <$> modules_below where
- (td_map, lookup_node) = external_trans mg
- modules_below =
- allReachable td_map <$> lookup_node nk
-
--- | Return all nodes reachable from all of the given keys.
-emgReachableLoopMany :: ExternalModuleGraph -> [ExternalKey] -> [ExternalGraphNode]
-emgReachableLoopMany mg nk = map node_payload modules_below where
- (td_map, lookup_node) = external_trans mg
- modules_below =
- allReachableMany td_map (mapMaybe lookup_node nk)
-
---------------------------------------------------------------------------------
--- * Internals
---------------------------------------------------------------------------------
-
--- | Turn a list of graph nodes into an efficient queriable graph.
--- The first boolean parameter indicates whether nodes corresponding to hs-boot files
--- should be collapsed into their relevant hs nodes.
-externalGraphNodes :: Bool
- -> [ExternalGraphNode]
- -> (Graph ExternalNode, ExternalKey -> Maybe ExternalNode)
-externalGraphNodes drop_hs_boot_nodes summaries =
- (graphFromEdgedVerticesUniq nodes, lookup_node)
- where
- -- Map from module to extra boot summary dependencies which need to be merged in
- (boot_summaries, nodes) = bimap M.fromList id $ partitionWith go numbered_summaries
-
- where
- go (s, key) =
- case s of
- NodeHomePackage (ModNodeKeyWithUid (GWIB mn IsBoot) uid) _deps | drop_hs_boot_nodes
- -- Using emgNodeDeps here converts dependencies on other
- -- boot files to dependencies on dependencies on non-boot files.
- -> Left (mkModule uid mn, emgNodeDeps drop_hs_boot_nodes s)
- _ -> normal_case
- where
- normal_case =
- let lkup_key =
- case s of
- NodeHomePackage (ModNodeKeyWithUid (GWIB mn IsBoot) uid) _deps
- -> Just $ mkModule uid mn
- _ -> Nothing
-
- extra = (lkup_key >>= \key -> M.lookup key boot_summaries)
-
- in Right $ DigraphNode s key $ out_edge_keys $
- (fromMaybe [] extra
- ++ emgNodeDeps drop_hs_boot_nodes s)
-
- numbered_summaries = zip summaries [1..]
-
- lookup_node :: ExternalKey -> Maybe ExternalNode
- lookup_node key = M.lookup key node_map
-
- lookup_key :: ExternalKey -> Maybe Int
- lookup_key = fmap node_key . lookup_node
-
- node_map :: M.Map ExternalKey ExternalNode
- node_map =
- M.fromList [ (emgNodeKey s, node)
- | node <- nodes
- , let s = node_payload node
- ]
-
- out_edge_keys :: [ExternalKey] -> [Int]
- out_edge_keys = mapMaybe lookup_key
- -- If we want keep_hi_boot_nodes, then we do lookup_key with
- -- IsBoot; else False
-
-instance Outputable ExternalGraphNode where
- ppr = \case
- NodeHomePackage mk ds -> text "NodeHomePackage" <+> ppr mk <+> ppr ds
- NodeExternalPackage mk ds -> text "NodeExternalPackage" <+> ppr mk <+> ppr ds
-
-instance Outputable ExternalKey where
- ppr = \case
- ExternalModuleKey mk -> text "ExternalModuleKey" <+> ppr mk
- ExternalPackageKey uid -> text "ExternalPackageKey" <+> ppr uid
-
-instance Outputable ExternalModuleGraph where
- ppr ExternalModuleGraph{external_nodes, external_fully_loaded}
- = text "ExternalModuleGraph" <+> ppr external_nodes <+> ppr external_fully_loaded
=====================================
compiler/GHC/Unit/Module/Graph.hs
=====================================
@@ -41,6 +41,8 @@ module GHC.Unit.Module.Graph
, ModuleNodeInfo(..)
, moduleNodeInfoModule
+ , moduleNodeInfoUnitId
+ , moduleNodeInfoMnwib
, moduleNodeInfoModuleName
, moduleNodeInfoModNodeKeyWithUid
, moduleNodeInfoHscSource
@@ -48,7 +50,7 @@ module GHC.Unit.Module.Graph
, isBootModuleNodeInfo
-- * Module graph operations
, lengthMG
-
+ , isEmptyMG
-- ** 'ModSummary' operations
--
-- | A couple of operations on the module graph allow access to the
@@ -100,6 +102,10 @@ module GHC.Unit.Module.Graph
, ModNodeKey
, ModNodeKeyWithUid(..)
, mnkToModule
+ , moduleToMnk
+ , mnkToInstalledModule
+ , installedModuleToMnk
+ , mnkIsBoot
, msKey
, mnKey
, miKey
@@ -310,7 +316,7 @@ checkFixedModuleInvariant node_types node = case node of
_ -> Nothing
-{- Note [Modules Types in the ModuleGraph]
+{- Note [Module Types in the ModuleGraph]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Modules can be one of two different types in the module graph.
@@ -365,6 +371,14 @@ isBootModuleNodeInfo (ModuleNodeCompile ms) = isBootSummary ms
moduleNodeInfoModuleName :: ModuleNodeInfo -> ModuleName
moduleNodeInfoModuleName m = moduleName (moduleNodeInfoModule m)
+moduleNodeInfoUnitId :: ModuleNodeInfo -> UnitId
+moduleNodeInfoUnitId (ModuleNodeFixed key _) = mnkUnitId key
+moduleNodeInfoUnitId (ModuleNodeCompile ms) = ms_unitid ms
+
+moduleNodeInfoMnwib :: ModuleNodeInfo -> ModuleNameWithIsBoot
+moduleNodeInfoMnwib (ModuleNodeFixed key _) = mnkModuleName key
+moduleNodeInfoMnwib (ModuleNodeCompile ms) = ms_mnwib ms
+
-- | Collect the immediate dependencies of a ModuleGraphNode,
-- optionally avoiding hs-boot dependencies.
-- If the drop_hs_boot_nodes flag is False, and if this is a .hs and there is
@@ -425,6 +439,9 @@ instance Ord ModuleGraphNode where
lengthMG :: ModuleGraph -> Int
lengthMG = length . mg_mss
+isEmptyMG :: ModuleGraph -> Bool
+isEmptyMG = null . mg_mss
+
--------------------------------------------------------------------------------
-- ** ModSummaries
--------------------------------------------------------------------------------
=====================================
compiler/GHC/Unit/Module/ModNodeKey.hs
=====================================
@@ -1,4 +1,11 @@
-module GHC.Unit.Module.ModNodeKey ( ModNodeKeyWithUid(..), mnkToModule, mnkIsBoot ) where
+module GHC.Unit.Module.ModNodeKey
+ ( ModNodeKeyWithUid(..)
+ , mnkToModule
+ , moduleToMnk
+ , mnkIsBoot
+ , mnkToInstalledModule
+ , installedModuleToMnk
+ ) where
import GHC.Prelude
import GHC.Utils.Outputable
@@ -7,12 +14,22 @@ import GHC.Unit.Types
data ModNodeKeyWithUid = ModNodeKeyWithUid { mnkModuleName :: !ModuleNameWithIsBoot
, mnkUnitId :: !UnitId } deriving (Eq, Ord)
-mnkIsBoot :: ModNodeKeyWithUid -> IsBootInterface
-mnkIsBoot (ModNodeKeyWithUid mnwib _) = gwib_isBoot mnwib
-
mnkToModule :: ModNodeKeyWithUid -> Module
mnkToModule (ModNodeKeyWithUid mnwib uid) = Module (RealUnit (Definite uid)) (gwib_mod mnwib)
+mnkToInstalledModule :: ModNodeKeyWithUid -> InstalledModule
+mnkToInstalledModule (ModNodeKeyWithUid mnwib uid) = Module uid (gwib_mod mnwib)
+
+-- | Already InstalledModules are always NotBoot
+installedModuleToMnk :: InstalledModule -> ModNodeKeyWithUid
+installedModuleToMnk mod = ModNodeKeyWithUid (GWIB (moduleName mod) NotBoot) (moduleUnit mod)
+
+moduleToMnk :: Module -> IsBootInterface -> ModNodeKeyWithUid
+moduleToMnk mod is_boot = ModNodeKeyWithUid (GWIB (moduleName mod) is_boot) (moduleUnitId mod)
+
+mnkIsBoot :: ModNodeKeyWithUid -> IsBootInterface
+mnkIsBoot (ModNodeKeyWithUid mnwib _) = gwib_isBoot mnwib
+
instance Outputable ModNodeKeyWithUid where
ppr (ModNodeKeyWithUid mnwib uid) = ppr uid <> colon <> ppr mnwib
=====================================
compiler/ghc.cabal.in
=====================================
@@ -526,6 +526,7 @@ Library
GHC.Driver.MakeSem
GHC.Driver.Main
GHC.Driver.Make
+ GHC.Driver.Messager
GHC.Driver.MakeAction
GHC.Driver.MakeFile
GHC.Driver.Monad
@@ -956,7 +957,6 @@ Library
GHC.Unit.Module.Env
GHC.Unit.Module.Graph
GHC.Unit.Module.ModNodeKey
- GHC.Unit.Module.External.Graph
GHC.Unit.Module.Imported
GHC.Unit.Module.Location
GHC.Unit.Module.ModDetails
=====================================
testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs
=====================================
@@ -0,0 +1,102 @@
+{-# LANGUAGE RecordWildCards #-}
+module Main where
+
+import GHC
+import GHC.Driver.Session
+import GHC.Driver.Monad
+import GHC.Driver.Env
+import GHC.Driver.Make (summariseFile)
+import GHC.Driver.Downsweep
+import GHC.Unit.Module.Graph
+import GHC.Unit.Module.ModSummary
+import GHC.Unit.Types
+import GHC.Unit.Module
+import GHC.Unit.Module.ModNodeKey
+import GHC.Types.SourceFile
+import System.Environment
+import Control.Monad (void, when)
+import Data.Maybe (fromJust)
+import Control.Exception (ExceptionWithContext(..), SomeException)
+import Control.Monad.Catch (handle, throwM)
+import Control.Exception.Context
+import GHC.Utils.Outputable
+import Data.List
+import GHC.Unit.Env
+import GHC.Unit.State
+import GHC.Tc.Utils.Monad
+import GHC.Iface.Env
+import GHC.Driver.Ppr
+import GHC.Unit.Home
+
+
+main :: IO ()
+main = do
+ [libdir] <- getArgs
+ runGhc (Just libdir) $ handle (\(ExceptionWithContext c e :: ExceptionWithContext SomeException) ->
+ liftIO $ putStrLn (displayExceptionContext c) >> print e >> throwM e) $ do
+
+ -- Set up session
+ dflags <- getSessionDynFlags
+ setSessionDynFlags (dflags { verbosity = 1 })
+ hsc_env <- getSession
+ setSession $ hscSetActiveUnitId mainUnitId hsc_env
+
+ -- Get ModSummaries for our test modules
+ msA <- getModSummaryFromTarget "T1A.hs"
+ msB <- getModSummaryFromTarget "T1B.hs"
+ msC <- getModSummaryFromTarget "T1C.hs"
+
+ let targets = [ Target (TargetModule (ms_mod_name msA)) True (moduleUnitId $ ms_mod msA) Nothing
+ , Target (TargetModule (ms_mod_name msB)) True (moduleUnitId $ ms_mod msB) Nothing
+ , Target (TargetModule (ms_mod_name msC)) True (moduleUnitId $ ms_mod msC) Nothing
+ ]
+
+ setTargets targets
+
+ -- Compile interfaces for our modules
+ load LoadAllTargets
+
+ hsc_env <- getSession
+ setSession $ hsc_env { hsc_dflags = (hsc_dflags hsc_env) { ghcMode = OneShot } }
+ hsc_env <- getSession
+
+
+ -- Create ModNodeKeys with unit IDs
+ let keyA = msKey msA
+ keyB = msKey msB
+ keyC = msKey msC
+
+ let mkGraph s = do
+ ([], nodes) <- downsweepFromRootNodes hsc_env mempty [] True DownsweepUseFixed s []
+ return $ mkModuleGraph nodes
+
+ graph <- liftIO $ mkGraph [ModuleNodeCompile msC]
+
+ liftIO $ putStrLn "loaded"
+ -- 1. Check that the module graph is valid
+ let invariantErrors = checkModuleGraph graph
+
+ case invariantErrors of
+ [] -> liftIO $ putStrLn "PASS Test passed"
+ errors -> do
+ liftIO $ putStrLn "FAIL Test failed - invariant violations"
+ liftIO $ putStrLn $ showSDoc dflags $ vcat (map ppr errors)
+
+ -- 2. Check that from the root, we can reach the "ghc-internal" package.
+ let ghcInternalPackage = NodeKey_ExternalUnit ghcInternalUnitId
+ let root = NodeKey_Module keyC
+ let reached = mgQuery graph root ghcInternalPackage
+ if not reached
+ then liftIO $ putStrLn "FAIL Test failed - cannot reach ghc-internal"
+ else liftIO $ putStrLn "PASS Test passed"
+
+
+
+ where
+
+ -- Helper to get ModSummary from a target file
+ getModSummaryFromTarget :: FilePath -> Ghc ModSummary
+ getModSummaryFromTarget file = do
+ hsc_env <- getSession
+ Right ms <- liftIO $ summariseFile hsc_env (DefiniteHomeUnit mainUnitId Nothing) mempty file Nothing Nothing
+ return ms
=====================================
testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout
=====================================
@@ -0,0 +1,6 @@
+[1 of 3] Compiling T1A ( T1A.hs, T1A.o )
+[2 of 3] Compiling T1B ( T1B.hs, T1B.o )
+[3 of 3] Compiling T1C ( T1C.hs, T1C.o )
+loaded
+PASS Test passed
+PASS Test passed
=====================================
testsuite/tests/ghc-api/fixed-nodes/all.T
=====================================
@@ -13,3 +13,11 @@ test('ModuleGraphInvariants',
],
compile_and_run,
['-package ghc'])
+
+test('InterfaceModuleGraph',
+ [extra_run_opts(f'"{config.libdir}"'),
+ extra_files(['T1A.hs', 'T1B.hs', 'T1C.hs']),
+ wasm_broken(25953)
+ ],
+ compile_and_run,
+ ['-package ghc'])
=====================================
testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs
=====================================
@@ -46,13 +46,8 @@ lookupModule :: ModuleName -- ^ Name of the module
-> TcPluginM Module
lookupModule mod_nm = do
hsc_env <- getTopEnv
- let dflags = hsc_dflags hsc_env
- let fopts = initFinderOpts dflags
- let fc = hsc_FC hsc_env
- let units = hsc_units hsc_env
let home_unit = hsc_home_unit hsc_env
- -- found_module <- findPluginModule fc fopts units home_unit mod_name
- found_module <- tcPluginIO $ findPluginModule fc fopts units (Just home_unit) mod_nm
+ found_module <- tcPluginIO $ findPluginModule hsc_env mod_nm
case found_module of
FoundModule h -> return (fr_mod h)
_ -> do
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d47bf7769758a1c8f65b66bb41b926c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d47bf7769758a1c8f65b66bb41b926c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T24782] template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`
by Teo Camarasu (@teo) 16 Apr '25
by Teo Camarasu (@teo) 16 Apr '25
16 Apr '25
Teo Camarasu pushed to branch wip/T24782 at Glasgow Haskell Compiler / GHC
Commits:
bbc2f110 by Teo Camarasu at 2025-04-16T17:14:16+01:00
template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`
These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
Resolves #24782
- - - - -
3 changed files:
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- testsuite/tests/interface-stability/template-haskell-exports.stdout
Changes:
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,6 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE Safe #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,16 +190,11 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
- addrToByteArrayName,
- addrToByteArray,
)
where
-import Data.Array.Byte
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
-import GHC.Exts
-import GHC.ST
import System.FilePath
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
@@ -211,17 +206,3 @@ makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
-
--- The following two defintions are copied from 'Data.Byte.Array'
--- in order to preserve the old export list of 'TH.Syntax'.
--- They will soon be removed as part of #24782.
-
-addrToByteArrayName :: Name
-addrToByteArrayName = 'addrToByteArray
-
-addrToByteArray :: Int -> Addr# -> ByteArray
-addrToByteArray (I# len) addr = runST $ ST $
- \s -> case newByteArray# len s of
- (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of
- s'' -> case unsafeFreezeByteArray# mb s'' of
- (# s''', ret #) -> (# s''', ByteArray ret #)
=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -13,6 +13,8 @@
* Remove the `Language.Haskell.TH.Lib.Internal` module. This module has long been deprecated, and exposes compiler internals.
Users should use `Language.Haskell.TH.Lib` instead, which exposes a stable version of this API.
+
+ * Remove `addrToByteArrayName` and `addrToByteArray` from `Language.Haskell.TH.Syntax`. These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
## 2.23.0.0
=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1369,7 +1369,7 @@ module Language.Haskell.TH.Quote where
quoteFile :: QuasiQuoter -> QuasiQuoter
module Language.Haskell.TH.Syntax where
- -- Safety: Trustworthy
+ -- Safety: Safe
type AnnLookup :: *
data AnnLookup = AnnLookupModule Module | AnnLookupName Name
type AnnTarget :: *
@@ -1780,8 +1780,6 @@ module Language.Haskell.TH.Syntax where
addModFinalizer :: Q () -> Q ()
addTempFile :: GHC.Internal.Base.String -> Q GHC.Internal.IO.FilePath
addTopDecls :: [Dec] -> Q ()
- addrToByteArray :: GHC.Internal.Types.Int -> GHC.Internal.Prim.Addr# -> Data.Array.Byte.ByteArray
- addrToByteArrayName :: Name
badIO :: forall a. GHC.Internal.Base.String -> GHC.Internal.Types.IO a
bindCode :: forall (m :: * -> *) a (r :: GHC.Internal.Types.RuntimeRep) (b :: TYPE r). GHC.Internal.Base.Monad m => m a -> (a -> Code m b) -> Code m b
bindCode_ :: forall (m :: * -> *) a (r :: GHC.Internal.Types.RuntimeRep) (b :: TYPE r). GHC.Internal.Base.Monad m => m a -> Code m b -> Code m b
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bbc2f11035915a3c29866af2e35f3b5…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bbc2f11035915a3c29866af2e35f3b5…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed new branch wip/T25965 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25965
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T24782] template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`
by Teo Camarasu (@teo) 16 Apr '25
by Teo Camarasu (@teo) 16 Apr '25
16 Apr '25
Teo Camarasu pushed to branch wip/T24782 at Glasgow Haskell Compiler / GHC
Commits:
67baf29c by Teo Camarasu at 2025-04-16T14:10:46+01:00
template-haskell: Remove `addrToByteArrayName` and `addrToByteArray`
These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
Resolves #24782
- - - - -
3 changed files:
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- testsuite/tests/interface-stability/template-haskell-exports.stdout
Changes:
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -1,6 +1,6 @@
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
-{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE Safe #-}
{-# LANGUAGE UnboxedTuples #-}
module Language.Haskell.TH.Syntax (
@@ -190,16 +190,11 @@ module Language.Haskell.TH.Syntax (
nothingName,
rightName,
trueName,
- addrToByteArrayName,
- addrToByteArray,
)
where
-import Data.Array.Byte
import GHC.Boot.TH.Lift
import GHC.Boot.TH.Syntax
-import GHC.Exts
-import GHC.ST
import System.FilePath
-- This module completely re-exports 'GHC.Boot.TH.Syntax',
@@ -211,17 +206,3 @@ makeRelativeToProject fp | isRelative fp = do
root <- getPackageRoot
return (root </> fp)
makeRelativeToProject fp = return fp
-
--- The following two defintions are copied from 'Data.Byte.Array'
--- in order to preserve the old export list of 'TH.Syntax'.
--- They will soon be removed as part of #24782.
-
-addrToByteArrayName :: Name
-addrToByteArrayName = 'addrToByteArray
-
-addrToByteArray :: Int -> Addr# -> ByteArray
-addrToByteArray (I# len) addr = runST $ ST $
- \s -> case newByteArray# len s of
- (# s', mb #) -> case copyAddrToByteArray# addr mb 0# len s' of
- s'' -> case unsafeFreezeByteArray# mb s'' of
- (# s''', ret #) -> (# s''', ByteArray ret #)
=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -13,6 +13,8 @@
* Remove the `Language.Haskell.TH.Lib.Internal` module. This module has long been deprecated, and exposes compiler internals.
Users should use `Language.Haskell.TH.Lib` instead, which exposes a stable version of this API.
+
+ * Remove `addrToByteArrayName` and `addrToByteArray` from `Language.Haskell.TH.Syntax`. These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
## 2.23.0.0
=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1780,8 +1780,6 @@ module Language.Haskell.TH.Syntax where
addModFinalizer :: Q () -> Q ()
addTempFile :: GHC.Internal.Base.String -> Q GHC.Internal.IO.FilePath
addTopDecls :: [Dec] -> Q ()
- addrToByteArray :: GHC.Internal.Types.Int -> GHC.Internal.Prim.Addr# -> Data.Array.Byte.ByteArray
- addrToByteArrayName :: Name
badIO :: forall a. GHC.Internal.Base.String -> GHC.Internal.Types.IO a
bindCode :: forall (m :: * -> *) a (r :: GHC.Internal.Types.RuntimeRep) (b :: TYPE r). GHC.Internal.Base.Monad m => m a -> (a -> Code m b) -> Code m b
bindCode_ :: forall (m :: * -> *) a (r :: GHC.Internal.Types.RuntimeRep) (b :: TYPE r). GHC.Internal.Base.Monad m => m a -> Code m b -> Code m b
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67baf29ca5cd3f3f786af2ad5978581…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67baf29ca5cd3f3f786af2ad5978581…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/splice-imports-2025] Explicit level imports 2025
by Matthew Pickering (@mpickering) 16 Apr '25
by Matthew Pickering (@mpickering) 16 Apr '25
16 Apr '25
Matthew Pickering pushed to branch wip/splice-imports-2025 at Glasgow Haskell Compiler / GHC
Commits:
5dd13cba by Matthew Pickering at 2025-04-16T12:25:08+01:00
Explicit level imports 2025
- - - - -
203 changed files:
- compiler/GHC.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/ghc.cabal.in
- docs/users_guide/exts/template_haskell.rst
- libraries/base/tests/IO/Makefile
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T21023.stderr
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dd13cba474d8c4a089d5706b827f2c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dd13cba474d8c4a089d5706b827f2c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/splice-imports-2025] Explicit level imports 2025
by Matthew Pickering (@mpickering) 16 Apr '25
by Matthew Pickering (@mpickering) 16 Apr '25
16 Apr '25
Matthew Pickering pushed to branch wip/splice-imports-2025 at Glasgow Haskell Compiler / GHC
Commits:
44968f5d by Matthew Pickering at 2025-04-16T12:23:42+01:00
Explicit level imports 2025
- - - - -
203 changed files:
- compiler/GHC.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/ghc.cabal.in
- docs/users_guide/exts/template_haskell.rst
- libraries/base/tests/IO/Makefile
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T21023.stderr
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44968f5df71512e5eae804a28f35c5c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/44968f5df71512e5eae804a28f35c5c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Register EpToken in Parser.PostProcess.Haddock (#22558)
by Marge Bot (@marge-bot) 16 Apr '25
by Marge Bot (@marge-bot) 16 Apr '25
16 Apr '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
05eb50df by Vladislav Zavialov at 2025-04-13T19:16:38-04:00
Register EpToken in Parser.PostProcess.Haddock (#22558)
This change allows us to reject more badly placed Haddock comments.
Examples:
module
-- | Bad comment for the module
T17544_kw where
data Foo -- | Bad comment for MkFoo
where MkFoo :: Foo
newtype Bar -- | Bad comment for MkBar
where MkBar :: () -> Bar
class Cls a
-- | Bad comment for clsmethod
where
clsmethod :: a
- - - - -
01944e5e by Vladislav Zavialov at 2025-04-13T19:17:21-04:00
Reject puns in T2T (#24153)
This patch implements pun detection in T2T. Consider:
x = 42
f, g :: forall a -> ...
f (type x) = g x
In accordance with the specification, the `g x` function call is renamed
as a term, so `x` refers to the top-level binding `x = 42`, not to the
type variable binding `type x` as one might expect.
This is somewhat counterintuitive because `g` expects a type argument.
Forbidding puns in T2T allows us to produce a helpful error message:
Test.hs:5:16: error: [GHC-09591]
Illegal punned variable occurrence in a required type argument.
The name ‘x’ could refer to:
‘x’ defined at Test.hs:3:1
‘x’ bound at Test.hs:5:9
This commit is a follow up to 0dfb1fa799af254c8a1e1045fc3996af2d57a613
where checking for puns was left as future work.
- - - - -
cc580552 by Vladislav Zavialov at 2025-04-13T19:18:02-04:00
Additional test cases for #12088, #13790
Extract more test cases from ticket discussions, including multi-module
examples. Follow up to 5712e0d646f611dfbfedfd7ef6dff3a18c016edb
- - - - -
d47bf776 by Matthew Pickering at 2025-04-14T16:44:41+01:00
driver: Use ModuleGraph for oneshot and --make mode
This patch uses the `hsc_mod_graph` field for both oneshot and --make
mode. Therefore, if part of the compiler requires usage of the module
graph, you do so in a uniform way for the two different modes.
The `ModuleGraph` describes the relationship between the modules in the
home package and units in external packages. The `ModuleGraph` can be
queried when information about the transitive closure of a package is
needed. For example, the primary use of the ModuleGraph from within the
compiler is in the loader, which needs to know the transitive closure of
a module so it can load all the relevant objects for evaluation.
In --make mode, downsweep computes the ModuleGraph before any
compilation starts.
In oneshot mode, a thunk is created at the start of compilation, which
when forced will compute the module graph beneath the current module.
The thunk is only forced at the moment when the user uses Template
Haskell.
Finally, there are some situations where we need to discover what
dependencies to load but haven't loaded a module graph at all. In this
case, there is a fallback which computes the transitive closure on the
fly and doesn't cache the result. Presumably if you are going to call
getLinkDeps a lot, you would compute the right ModuleGraph before you
started.
Importantly, this removes the ExternalModuleGraph abstraction. This was quite
awkward to work with since it stored information about the home package
inside the EPS.
This patch will also be very useful when implementing explicit level
imports, which requires more significant use of the module graph in
order to determine which level instances are available at.
Towards #25795
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
MultiLayerModulesTH_OneShot
-------------------------
- - - - -
65470211 by sheaf at 2025-04-16T05:12:10-04:00
base: remove .Internal modules (e.g. GHC.TypeLits)
This commit removes the following internal modules from base,
as per CLC proposal 217:
- GHC.TypeNats.Internal
- GHC.TypeLits.Internal
- GHC.ExecutionStack.Internal
Fixes #25007
- - - - -
58 changed files:
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeAction.hs
- + compiler/GHC/Driver/Messager.hs
- compiler/GHC/Driver/Pipeline.hs-boot
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Unit/External.hs
- compiler/GHC/Unit/Finder.hs
- − compiler/GHC/Unit/Module/External/Graph.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/ModNodeKey.hs
- compiler/ghc.cabal.in
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- − libraries/base/src/GHC/ExecutionStack/Internal.hs
- − libraries/base/src/GHC/TypeLits/Internal.hs
- − libraries/base/src/GHC/TypeNats/Internal.hs
- + testsuite/tests/dependent/should_compile/T12088f.hs
- + testsuite/tests/dependent/should_compile/T12088g.hs
- + testsuite/tests/dependent/should_compile/T12088i.hs
- + testsuite/tests/dependent/should_compile/T12088j.hs
- + testsuite/tests/dependent/should_compile/T12088mm1.hs
- + testsuite/tests/dependent/should_compile/T12088mm1_helper.hs
- + testsuite/tests/dependent/should_compile/T12088mm2.hs
- + testsuite/tests/dependent/should_compile/T12088mm2_helper.hs
- + testsuite/tests/dependent/should_compile/T12088mm3.hs
- + testsuite/tests/dependent/should_compile/T12088mm3_helper.hs
- + testsuite/tests/dependent/should_compile/T13790.hs
- testsuite/tests/dependent/should_compile/all.T
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.hs
- + testsuite/tests/ghc-api/fixed-nodes/InterfaceModuleGraph.stdout
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/plugins/defaulting-plugin/DefaultLifted.hs
- + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.hs
- + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a07b9fac8a3c81a06bfd07ab7b070…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a07b9fac8a3c81a06bfd07ab7b070…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/splice-imports-2025] Explicit level imports 2025
by Matthew Pickering (@mpickering) 16 Apr '25
by Matthew Pickering (@mpickering) 16 Apr '25
16 Apr '25
Matthew Pickering pushed to branch wip/splice-imports-2025 at Glasgow Haskell Compiler / GHC
Commits:
d0968e02 by Matthew Pickering at 2025-04-16T10:03:10+01:00
Explicit level imports 2025
- - - - -
203 changed files:
- compiler/GHC.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- compiler/ghc.cabal.in
- docs/users_guide/exts/template_haskell.rst
- libraries/base/tests/IO/Makefile
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T21023.stderr
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d0968e0209ac17d91c60d67c0414675…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d0968e0209ac17d91c60d67c0414675…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/supersven/riscv-fix-switch-jump-tables] 10 commits: hadrian: Make ghcWithInterpreter the universal source of truth about...
by Sven Tennie (@supersven) 16 Apr '25
by Sven Tennie (@supersven) 16 Apr '25
16 Apr '25
Sven Tennie pushed to branch wip/supersven/riscv-fix-switch-jump-tables at Glasgow Haskell Compiler / GHC
Commits:
6a3e38f5 by Andreas Klebinger at 2025-04-11T15:13:53-04:00
hadrian: Make ghcWithInterpreter the universal source of truth about availability of the interpreter
We were doing some ad-hoc checks in different places in hadrian to
determine whether we supported the interprter or not. Now this check if
confined to one function, `ghcWithInterpreter`, and all the places which
use this information consult `ghcWithInterpreter` to determine what to
do.
Fixes #25533.
- - - - -
207de6f1 by Matthew Pickering at 2025-04-11T15:14:37-04:00
testsuite: Fix running TH tests with profiled dynamic compiler
Previously, I had failed to update the ghc_th_way_flags logic for the
profiled dynamic compiler.
In addition to this `ghc_dynamic` was incorrectly set for profiled
dynamic compiler.
I also updated MultiLayerModulesTH_OneShot test to work for any compiler
linkage rather than just dynamic.
Fixes #25947
-------------------------
Metric Decrease:
MultiLayerModulesTH_Make
-------------------------
- - - - -
5455f2b9 by Matthew Pickering at 2025-04-12T08:31:36-04:00
driver: Add support for "Fixed" nodes in the ModuleGraph
A fixed node in the module graph is one which we presume is already
built. It's therefore up to the user to make sure that the interface
file and any relevant artifacts are available for a fixed node.
Fixed/Compile nodes are represented by the ModuleNodeInfo type, which
abstracts the common parts of Fixed/Compile nodes with accessor
functions of type `ModuleNodeInfo -> ...`.
Fixed nodes can only depend on other fixed nodes. This invariant can be
checked by the function `checkModuleGraph` or `mkModuleGraphChecked`.
--make mode is modified to work with fixed mode. In order to "compile" a
fixed node, the artifacts are just loaded into the HomePackageTable.
Currently nothing in the compiler will produce Fixed nodes but this is
tested with the FixedNodes GHC API test.
In subsequent patches we are going to remove the ExternalModuleGraph and
use Fixed nodes for modules in the module graph in oneshot mode.
Fixes #25920
- - - - -
ad64d5c2 by Cheng Shao at 2025-04-12T08:32:19-04:00
ci: remove manual case of ghc-wasm-meta downstream testing jobs
This patch removes the manual case of ghc-wasm-meta downstream testing
jobs; now the only way of including them in the pipeline and running
them is via the test-wasm label.
The reason of the removal is it proves to be problematic for MRs with
only the wasm label; the wasm job would succeed, then the pipeline
status would be waiting for manual action instead of succeeding. There
needs to be separate jobs for the label-triggered and manual-triggered
cases, but I don't think it's worth that extra complexity, the
label-triggered case is already sufficient.
- - - - -
b34890c7 by Vladislav Zavialov at 2025-04-13T01:08:21+03:00
Fix EmptyCase panic in tcMatches (#25960)
Due to faulty reasoning in Note [Pattern types for EmptyCase],
tcMatches was too keen to panic.
* Old (incorrect) assumption: pat_tys is a singleton list.
This does not hold when \case{} is checked against a function type
preceded by invisible forall. See the new T25960 test case.
* New (hopefully correct) assumption: vis_pat_tys is a singleton list.
This should follow from:
checkArgCounts :: MatchGroup GhcRn ... -> TcM VisArity
checkArgCounts (MG { mg_alts = L _ [] })
= return 1
...
- - - - -
84806ebc by Vladislav Zavialov at 2025-04-13T11:40:08-04:00
Remove unused type: TokenLocation
- - - - -
05eb50df by Vladislav Zavialov at 2025-04-13T19:16:38-04:00
Register EpToken in Parser.PostProcess.Haddock (#22558)
This change allows us to reject more badly placed Haddock comments.
Examples:
module
-- | Bad comment for the module
T17544_kw where
data Foo -- | Bad comment for MkFoo
where MkFoo :: Foo
newtype Bar -- | Bad comment for MkBar
where MkBar :: () -> Bar
class Cls a
-- | Bad comment for clsmethod
where
clsmethod :: a
- - - - -
01944e5e by Vladislav Zavialov at 2025-04-13T19:17:21-04:00
Reject puns in T2T (#24153)
This patch implements pun detection in T2T. Consider:
x = 42
f, g :: forall a -> ...
f (type x) = g x
In accordance with the specification, the `g x` function call is renamed
as a term, so `x` refers to the top-level binding `x = 42`, not to the
type variable binding `type x` as one might expect.
This is somewhat counterintuitive because `g` expects a type argument.
Forbidding puns in T2T allows us to produce a helpful error message:
Test.hs:5:16: error: [GHC-09591]
Illegal punned variable occurrence in a required type argument.
The name ‘x’ could refer to:
‘x’ defined at Test.hs:3:1
‘x’ bound at Test.hs:5:9
This commit is a follow up to 0dfb1fa799af254c8a1e1045fc3996af2d57a613
where checking for puns was left as future work.
- - - - -
cc580552 by Vladislav Zavialov at 2025-04-13T19:18:02-04:00
Additional test cases for #12088, #13790
Extract more test cases from ticket discussions, including multi-module
examples. Follow up to 5712e0d646f611dfbfedfd7ef6dff3a18c016edb
- - - - -
0f976bb8 by Sven Tennie at 2025-04-16T08:03:27+00:00
RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738)
J_TBL result in local jumps, there should not deallocate stack slots
(see Note [extra spill slots].)
J is for non-local jumps, these may need to deallocate stack slots.
- - - - -
70 changed files:
- .gitlab-ci.yml
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Parser/Annotation.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/ModNodeKey.hs
- ghc/GHCi/UI.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Packages.hs
- testsuite/config/ghc
- testsuite/driver/testlib.py
- testsuite/mk/boilerplate.mk
- testsuite/tests/backpack/should_fail/bkpfail51.stderr
- + testsuite/tests/dependent/should_compile/T12088f.hs
- + testsuite/tests/dependent/should_compile/T12088g.hs
- + testsuite/tests/dependent/should_compile/T12088i.hs
- + testsuite/tests/dependent/should_compile/T12088j.hs
- + testsuite/tests/dependent/should_compile/T12088mm1.hs
- + testsuite/tests/dependent/should_compile/T12088mm1_helper.hs
- + testsuite/tests/dependent/should_compile/T12088mm2.hs
- + testsuite/tests/dependent/should_compile/T12088mm2_helper.hs
- + testsuite/tests/dependent/should_compile/T12088mm3.hs
- + testsuite/tests/dependent/should_compile/T12088mm3_helper.hs
- + testsuite/tests/dependent/should_compile/T13790.hs
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/driver/T20459.stderr
- testsuite/tests/driver/T24196/T24196.stderr
- testsuite/tests/driver/T24275/T24275.stderr
- + testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- + testsuite/tests/ghc-api/fixed-nodes/FixedNodes.stdout
- + testsuite/tests/ghc-api/fixed-nodes/Makefile
- + testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- + testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.stdout
- + testsuite/tests/ghc-api/fixed-nodes/T1.hs
- + testsuite/tests/ghc-api/fixed-nodes/T1A.hs
- + testsuite/tests/ghc-api/fixed-nodes/T1B.hs
- + testsuite/tests/ghc-api/fixed-nodes/T1C.hs
- + testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.hs
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/perf/compiler/Makefile
- testsuite/tests/perf/compiler/all.T
- + testsuite/tests/typecheck/should_compile/T25960.hs
- testsuite/tests/typecheck/should_compile/all.T
- + testsuite/tests/typecheck/should_fail/T25004k.hs
- + testsuite/tests/typecheck/should_fail/T25004k.stderr
- testsuite/tests/typecheck/should_fail/all.T
- + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.hs
- + testsuite/tests/vdq-rta/should_fail/T23738_fail_pun.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
- utils/haddock/haddock-api/src/Haddock/Interface.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07a15e2ab1d2065d7080ba796fd76d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07a15e2ab1d2065d7080ba796fd76d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/supersven/riscv-fix-switch-jump-tables] 144 commits: iface: Store flags in interface files
by Sven Tennie (@supersven) 16 Apr '25
by Sven Tennie (@supersven) 16 Apr '25
16 Apr '25
Sven Tennie pushed to branch wip/supersven/riscv-fix-switch-jump-tables at Glasgow Haskell Compiler / GHC
Commits:
44bf5fa1 by Matthew Pickering at 2025-03-07T13:48:18+00:00
iface: Store flags in interface files
When reporting the reason why a module is recompiled (using
`-dump-hi-diffs`), it is much more informative to inform the user about
which flag exactly has changed, rather than just an opaque reference to
a hash.
Now, when the user enables `-fwrite-if-self-recomp-flags`
there is a difference the precise part of the flags is
reported:
```
codegen flags changed:
before: [Opt_NoTypeableBinds, Opt_OmitYields]
after: [Opt_NoTypeableBinds, Opt_OmitYields, Opt_DictsStrict]
```
Fixes #25571
- - - - -
324222bd by Oleg Grenrus at 2025-03-08T08:50:18-05:00
Run fix-whitespace on compiler/
https://hackage.haskell.org/package/fix-whitespace
IMO this should be included into lint suite
- - - - -
1e53277a by sheaf at 2025-03-08T16:32:25-05:00
Allow defaulting of representational equalities
This commit generalises the defaulting of equality constraints that
was introduced in 663daf8d (with follow-up in 6863503c) to allow
the defaulting of *representational* equality constraints.
Now we default a representational equality
ty1 ~R# ty2
by unifying ty1 ~# ty2.
This allows the following defaulting to take place:
- Coercible alpha[tau] Int ==> alpha := Int
- Coercible (IO beta[tau]) (IO Char) ==> beta := Char
See Note [Defaulting representational equalities] in GHC.Tc.Solver.Default
for more details.
Fixes #21003
- - - - -
d6c40afc by Andreas Klebinger at 2025-03-08T16:33:02-05:00
Revert "Use `Infinite` in unique generation, and clean up some other partial uni patterns as well."
This reverts commit 643dd3d86968c527ba07ece9cc337728dbdfe2a0.
As described in #25817 this commit introduced a subtle bug in AArch64
code generation. So for the time being I will simply revert it
wholesale.
- - - - -
68310e11 by Andreas Klebinger at 2025-03-08T16:33:39-05:00
Properly describe acceptance window for stat tests.
The relative metric is already in %, so no need to multiply by 100.
- - - - -
cca68421 by Cheng Shao at 2025-03-08T22:04:42-05:00
wasm: do not use wasm type reflection in dyld
The wasm dynamic linker used to depend on v8's experimental wasm type
reflection support to generate stub functions when treating GOT.func
items that aren't exported by any loaded library yet. However, as we
work towards wasm ghci browser mode (#25399), we need to ensure the
wasm dyld logic is portable across browsers. So this commit removes
the usage of wasm type reflection in wasm dyld, and it shall only be
added many months later when this feature is widely available in
browsers.
- - - - -
75fcc5c9 by Cheng Shao at 2025-03-08T22:05:19-05:00
wasm: don't create a wasm global for dyld poison
There's a much more efficient way to convert an unsigned i32 to a
signed one. Thanks, o3-mini-high.
- - - - -
fd40eaa1 by Cheng Shao at 2025-03-08T22:05:19-05:00
wasm: revamp JSFFI internal implementation and documentation
This patch revamps the wasm backend's JSFFI internal implementation
and documentation:
- `JSValManager` logic to allocate a key is simplified to simple
bumping. According to experiments with all major browsers, the
internal `Map` would overflow the heap much earlier before we really
exhaust the 32-bit key space, so there's no point in the extra
complexity.
- `freeJSVal` is now idempotent and safe to call more than once. This
is achieved by attaching the `StablePtr#` to the `JSVal#` closure
and nullifying it when calling `freeJSVal`, so the same stable
pointer cannot be double freed.
- `mkWeakJSVal` no longer exposes the internal `Weak#` pointer and
always creates a new `Weak#` on the fly. Otherwise by finalizing
that `Weak#`, user could accidentally drop the `JSVal`, but
`mkWeakJSVal` is only supposed to create a `Weak` that observes the
`JSVal`'s liveliness without actually interfering it.
- `PromisePendingException` is no longer exported since it's never
meant to be caught by user code; it's a severe bug if it's actually
raised at runtime.
- Everything exported by user-facing `GHC.Wasm.Prim` now has proper
haddock documentation.
- Note [JSVal representation for wasm] has been updated to reflect the
new JSVal# memory layout.
- - - - -
cbae3708 by Ben Gamari at 2025-03-11T06:09:58-04:00
users guide: Fix typo
- - - - -
1951eb7a by Ben Gamari at 2025-03-11T06:10:35-04:00
testsuite: Don't count fragile passes as failures in JUnit output
As noted in #25806, the testsuite driver's JUnit output
previously considered passes of fragile tests to be failures. Fix this.
Closes #25806.
- - - - -
589f40b9 by Matthew Pickering at 2025-03-11T06:11:11-04:00
Use panic rather than error in expectJust
Otherwise, we would not get a callstack printed out when the exception
occurs.
Fixes #25829
- - - - -
d450e88e by sheaf at 2025-03-11T06:42:59-04:00
Solve Wanted quantified constraints from Givens
This commit ensures we directly solve Wanted quantified constraints from
matching inert Given quantified constraints,instead of going through the
trouble of emitting an implication constraint and processing that.
This is not just an optimisation; it makes our lives easier when
generating RULEs for specialisation.
See Note [Solving Wanted QCs from Given QCs] for details
Fixes #25758
- - - - -
48daaf53 by Ben Gamari at 2025-03-11T06:42:59-04:00
testsuite: Add testcase for #25577
- - - - -
d2ffb0ce by Ben Gamari at 2025-03-11T06:42:59-04:00
testsuite/ghc-api: Eliminate Makefile usage from various GHC API tests
These tests can be expressed perfectly well using the testsuite driver
itself.
- - - - -
2275b642 by Ben Gamari at 2025-03-11T06:42:59-04:00
rts/linker/MachO: Assert that GOT relocations have GOT entries
In #25577 we found that some GOT relocation types were not being given
relocation entries. Add assertions to catch this sort of failure in the
future.
- - - - -
8c96bcb4 by Ben Gamari at 2025-03-11T06:42:59-04:00
rts/linker/MachO: Account for internal GOT references in GOT construction
Previously we failed to give GOT slots to symbols which were referred to
by GOT relocations in the same module. This lead to #25577.
Fix this by explicitly traversing relocation lists and maintaining a
`needs_got` flag for each symbol.
Fixes #25577.
- - - - -
7b84c588 by Vladislav Zavialov at 2025-03-11T06:43:02-04:00
One list in ConPat (part of #25127)
This patch changes PrefixCon to use one list instead of two:
-data HsConDetails tyarg arg rec
- = PrefixCon [tyarg] [arg]
+data HsConDetails arg rec
+ = PrefixCon [arg]
| RecCon rec
| InfixCon arg arg
The [tyarg] list is now gone. To understand the effect of this change,
recall that there are three instantiations of HsConDetails:
1. type HsConPatDetails p =
HsConDetails (HsConPatTyArg (NoGhcTc p)) -- tyarg
(LPat p) -- arg
(HsRecFields p (LPat p)) -- rec
2. type HsConDeclH98Details pass =
HsConDetails Void -- tyarg
(HsScaled pass (LBangType pass)) -- arg
(XRec pass [LConDeclField pass]) -- rec
3. type HsPatSynDetails pass =
HsConDetails Void -- tyarg
(LIdP pass) -- arg
[RecordPatSynField pass] -- rec
In cases (2) and (3), tyarg was instantiated to Void, so the [tyarg]
list was always empty. Its removal is basically a no-op.
The interesting case is (1), which is used in ConPat to represent
pattern matching of the form (MkE @tp1 @tp2 p1 p2).
With this patch, its representation is changed as follows:
ConPat "MkE" [tp1, tp2] [p1, p2] -- old
ConPat "MkE" [InvisP tp1, InvisP tp2, p1, p2] -- new
The new mixed-list representation is consintent with lambdas, where
InvisP is already used to deal with \ @tp1 @tp2 p1 p2 -> body.
The immediate effect of the new representation is an improvement to
error messages. Consider the pattern (Con x @t y). Previously it
resulted in a parse error because @t could not occur after x. Now it is
reported as [GHC-14964]. Test case: TyAppPat_MisplacedApplication.
In the long term, this is intended as preparation for #18389 and #25127,
which would make (Con x @t y) potentially valid, e.g. if its type is
Con :: forall a -> forall b. (a, b) -> T
The TH AST is left unchanged for the moment to avoid breakage.
- - - - -
cce869ea by Vladislav Zavialov at 2025-03-11T06:43:02-04:00
Error message with EmptyCase and RequiredTypeArguments (#25004)
Fix a panic triggered by a combination of \case{} and forall t ->
ghci> let f :: forall (xs :: Type) -> (); f = \case {}
panic! (the 'impossible' happened)
GHC version 9.10.1:
Util: only
The new error message looks like this:
ghci> let f :: forall (xs :: Type) -> (); f = \case {}
<interactive>:5:41: error: [GHC-48010]
• Empty list of alternatives in \case expression
checked against a forall-type: forall xs -> ...
This is achieved as follows:
* A new data type, BadEmptyCaseReason, is now used to describe
why an empty case has been rejected. Used in TcRnEmptyCase.
* HsMatchContextRn is passed to tcMatches, so that the type checker
can attach the syntactic context to the error message.
* tcMatches now rejects type arguments if the list of alternatives is
empty. This is what fixes the bug.
- - - - -
37d8b50b by sheaf at 2025-03-11T06:43:06-04:00
user's guide: consolidate defaulting documentation
This commit adds a new section on defaulting, which consolidates various
parts of documentation surrounding defaulting into one central place.
It explains type class defaulting in detail, extensions to it with
OverloadedStrings, NamedDefaults and ExtendedDefaultRules, as well
as other defaulting mechanisms (e.g. kind-based defaulting such as
RuntimeRep defaulting, and defaulting of equalities).
- - - - -
0c9fd8d4 by sheaf at 2025-03-11T06:43:06-04:00
user's guide: flesh out XOverloadedStrings docs
This commit extends the documentation of the OverloadedStrings extension
with some usage information, in particular suggestions to:
- use default declarations, such as `default (Text)` or
`default IsString(Text)` (with the NamedDefaults extension),
- enable the ExtendedDefaultRules extension to relax the requirement
that a defaultable type variable must only appear in unary standard
classes
Fixes #23388
- - - - -
2df171d4 by sheaf at 2025-03-11T06:43:06-04:00
user's guide: NamedDefaults vs ExtendedDefaultRules
This commit clarifies the defaulting rules with NamedDefaults,
in particular in situations where a type variable appears in other
constraints than standard/unary constraints.
- - - - -
77df05d0 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Take into account all flags when computing iface_hash
The "interface hash" should contain a hash of everything in the
interface file. We are not doing that yet but at least a start is to
include a hash of everything in `mi_self_recomp`, rather than just
`mi_src_hash` and `mi_usages`.
In particular, this fixes #25837, a bug where we should recompile a
`dyn_hi` file but fail to do so.
- - - - -
48b8f110 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Pass -fPIC to dynamicToo001 test to avoid platform dependence issues
On darwin platforms, `-fPIC` is always enabled but on linux it is only
enabled in the dynamic flavour. This can cause a difference in
interface files (see #25836).
The purpose of this test isn't to test module A recompilation, so we
avoid this platform dependency by always passing `-fPIC`.
- - - - -
03c72f01 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Remove mi_used_th field from interface files
In the distant past, recompilation checking was disabled for interfaces which used
TemplateHaskell, but for several years now recompilation checking has
been more fine-grained. This has rendered this field unused and
lingering in an interface file.
- - - - -
6bb0e261 by Matthew Pickering at 2025-03-11T06:43:07-04:00
Remove mi_hpc field from interface files
The `mi_hpc` field is not used for anything as far as I can discern so
there is no reason to record in the private interface of a module that
there are modules in the transitive closure which use `hpc`.
You can freely mix modules which use `-fhpc` and ones which don't.
Whether to recompile a module due to `-fhpc` being passed to the module
itself is determined in `fingerprintDynFlags`.
- - - - -
b6d5b091 by Simon Peyton Jones at 2025-03-11T22:39:23-04:00
We can't UNPACK multi-constructor GADTs
This MR fixes #25672
See Note [Unpacking GADTs and existentials] in GHC.Types.Id.Make
- - - - -
8eae151d by Teo Camarasu at 2025-03-11T22:40:00-04:00
template-haskell: Add explicit exports lists to all remaining modules
- - - - -
db621b58 by Teo Camarasu at 2025-03-11T22:40:00-04:00
template-haskell: fix haddocks
It seems that we need a direct dependency on ghc-internal, otherwise
Haddock cannot find our haddocks
The bug seems to be caused by Hadrian because if I rebuild with
cabal-install (without this extra dependency) then I get accurate
Haddocks.
Resolves #25705
- - - - -
64ea68d9 by Ben Gamari at 2025-03-12T07:11:51-04:00
mk-ghcup-metadata: Clean up and add type annotations
Getting this file right has historically been quite painful as it is a
dynamically-typed script running only late in the release pipeline.
- - - - -
b3f80b07 by Ben Gamari at 2025-03-12T07:12:27-04:00
rts: Drop imports of pthreads functions in cmm sources
These are no longer used. I noticed these while looking for uses of
__PIC__ in Cmm sources.
- - - - -
915a6781 by Matthew Pickering at 2025-03-13T01:46:41-04:00
interfaces: Ensure that forceModIface deeply forces a ModIface
A ModIface is the result of compilation that we keep for a long time in
memory. Therefore, it's very important to manage what we are going to
retain and remove any external references to things which we might have
captured compilation.
If storing your ModIface in memory uses too much space, then store
less things or make it use a more efficient representation.
In the past there have been many space leak bugs by not sufficiently
forcing a ModIface (#15111)
This patch adds all the missing NFData instances for all the places I
could find where we weren't deeply forcing the structure.
- - - - -
24d373a6 by Matthew Craven at 2025-03-13T01:47:18-04:00
Add interface-stability test for ghc-prim
- - - - -
0cb1db92 by sheaf at 2025-03-14T13:11:44-04:00
Don't report used duplicate record fields as unused
This commit fixes the bug reported in #24035 in which the import of a
duplicate record field could be erroneously reported as unused.
The issue is that an import of the form "import M (fld)" can import
several different 'Name's, and we should only report an error if ALL
of those 'Name's are unused, not if ANY are.
Note [Reporting unused imported duplicate record fields]
in GHC.Rename.Names explains the solution to this problem.
Fixes #24035
- - - - -
f1830d74 by Matthew Pickering at 2025-03-14T13:12:21-04:00
binary: Directly copy ShortByteString to buffer rather than go via ByteString
This avoids allocating an intermediate bytestring. I just noticed on a
profile that `putFS` was allocating, and it seemed strange to me why
since it should just copy the contents of the FastString into the
already allocated buffer. It turned out we were going indirectly via a
ByteString.
Fixes #25861
- - - - -
b15fca2b by Matthew Pickering at 2025-03-15T05:36:40-04:00
iface: Store logical parts of ModIface together
The ModIface structure is divided into several logical parts:
1. mi_mod_info: Basic module metadata (name, version, etc.)
2. mi_public: The public interface of the module (the ABI), which includes:
- Exports, declarations, fixities, warnings, annotations
- Class and type family instances
- Rewrite rules and COMPLETE pragmas
- Safe Haskell and package trust information
- ABI hashes for recompilation checking
4. mi_self_recomp: Information needed for self-recompilation checking
(see Note [Self recompilation information in interface files])
5. mi_simplified_core: Optional simplified Core for bytecode generation
(only present when -fwrite-if-simplified-core is enabled)
6. mi_docs: Optional documentation (only present when -haddock is enabled)
7. mi_top_env: Information about the top-level environment of the original source
8. mi_ext_fields: Additional fields for extensibility
This structure helps organize the interface data according to its purpose and usage
patterns. Different parts of the compiler use different fields. By separating them
logically in the interface we can arrange to only deserialize the fields that are needed.
This patch also enforces the invariant that the fields of ModIface are
lazy. If you are keeping a ModIface on disk, then force it using
`forceModIface`. Otherwise, when the `ModIface` is read from disk, only
the parts which are needed from the interface will be deserialised.
In a follow-up patch I will tackle follow-up issues:
* Recompilation checking doesn't take into account exported named defaults (#25855)
* Recompilation checking does not take into account COMPLETE pragmas (#25854)
* mi_deps_ field in an interface is confused about whether the
information is for self-recompilation checking or part of the ABI
(#25844)
Fixes #25845
-------------------------
Metric Decrease:
MultiLayerModulesDefsGhciWithCore
-------------------------
- - - - -
c758cb71 by Ben Gamari at 2025-03-15T05:37:17-04:00
configure: Fix incorrect SettingsLlvmAsFlags value
Previously this was set to `LlvmAsCmd` rather than `LlvmAsFlags`,
resulting in #25856.
- - - - -
cfaaca14 by sheaf at 2025-03-18T20:05:03-04:00
Fix buglet in isEmptyWorkList
There was a missing case in GHC.Tc.Solver.InertSet.isEmptyWorkList; it
mistakenly ignored the 'wl_rw_eqs' field. This commit simply fixes that.
No test case.
- - - - -
9f9fe0b3 by sheaf at 2025-03-18T20:05:03-04:00
Add mapMaybeTM method to TrieMap class
This commit adds a new method to the TrieMap class, mapMaybeTM, and
adds implementations to all the instances.
mapMaybeTM is useful when filtering containers that contain other
containers.
- - - - -
393531ff by Simon Peyton Jones at 2025-03-18T20:05:03-04:00
Specialising expressions -- at last
This MR addresses #24359, which implements the GHC proposal 493 on SPECIALISE pragmas.
* The old code path (using SpecSig and SpecPrag) still exists.
* The new code path (using SpecSigE and SpecPragE) runs alongside it.
* All SPECIALISE pragmas are routed through the new code path, except
if you give multiple type sigs, when the old code path is still used.
* Main documentation: Note [Handling new-form SPECIALISE pragmas] in
GHC.Tc.Gen.Sig`
Thanks to @sheaf for helping with this MR.
The Big Thing is to introduce
{-# SPECIALISE forall x. f @Int x True #-}
where you can give type arguments and value argument to specialise; and
you can quantify them with forall, just as in Rules.
I thought it was going to be pretty simple, but it was a Long, Long Saga.
Highlights
* Overview Note [Handling new-form SPECIALISE pragmas] in GHC.Tc.Gen.Sig
- New data constructor `SpecSigE` in data type `L.H.S.Binds.Sig`
- New data construtor `SpecPragE` in data type `GHC.Hs.Binds.TcSpecPrag`
- Renamer: uses `checkSpecESigShape` to decide which function to assocate the
SPECIALISE pragma with
- Some of the action is in `GHC.Tc.Gen.Sig.tcSpecPrag`
- The rest is in `GHC.HsToCore.Binds.dsSpec`
* We use a new TcS mode, TcSFullySolve, when simplifying the Wanteds
that arise from the specialise expression. The mechanism is explained
in Note [TcSFullySolve] in GHC.Tc.Solver.Monad. The reason why we need
to do this is explained in Note [Fully solving constraints for specialisation]
in GHC.Tc.Gen.Sig.
* All of GHC.Tc.Gen.Rule is moved into GHC.Tc.Gen.Sig, because the code is
very closely related.
* The forall'd binders for SPECIALISE are the same as those for a RULE, so I
refactored, introducing data type `L.H.S.Binds.RuleBndrs`, with functions
to rename, zonk, typecheck it. I refactored this data type a bit; nicer now.
* On the LHS of RULES, or SPECIALISE, we want to disable the tricky mechanims
described in Note [Desugaring non-canonical evidence] in GHC.HsToCore.Expr.
Previously it wasn't fully disabled (just set to the empty set), and that
didn't quite work in the new regime.
* There are knock-on changes to Template Haskell.
* For the LHS of a RULE and a SPECIALISE expression, I wanted to simplify
it /without/ inlining the let-bindings for evidence variables. I added
a flag `so_inline` to the SimpleOpt optimiser to support this. The
entry point is `GHC.Core.SimpleOpt.simpleOptExprNoInline`
* Since forever we have had a hack for type variables on the LHS of
RULES. I took the opportunity to tidy this up. The main action is
in the zonker. See GHC.Tc.Zonk.Type Note [Free tyvars on rule LHS],
and especially data construtor `SkolemiseFlexi`
in data type `GHC.Tc.Zonk.Env.ZonkFlexi`
* Move `scopedSort` from GHC.Core.TyCo.FVs to GHC.Core.Predicate
Reason: it now works for Ids as well, and I wanted to use isEvVar,
which is defined in GHC.Core.Predicate
Avoiding module loops meant that instead of exporting GHC.Core.TyCo.Tidy
from GHC.Core.Type, modules now import the former directly.
I also took the opportunity to remove unused exports
from GHC.Core.Type.hs-boot
* Flag stuff:
- Add flag `-Wdeprecated-pragmas` and use it to control the warning when
using old-style SPECIALISE pragmas with multiple type ascriptions,
- Add flag `-Wuseless-specialisations` and use it to control the warning emitted
when GHC determines that a SPECIALISE pragma would have no effect. Don't
want if the SPECIALISE is SPECIALISE INLINE (#4444)
In response to #25389, we continue to generate these seemingly code for these
seemingly useless SPECIALISE pragmas
- Adds deprecations to Template Haskell `pragSpecD` and `pracSpecInlD`,
* Split up old-style SPECIALISE pragmas in GHC.Internal.Float,
GHC.Internal.Numeric, GHC.Internal.Real
* Remove useless SPECIALISE pragmas in Data.Array (updating the array submodule)
Smaller things:
- Update the Users Guide
- Add mention of the changes to the 9.14 release notes as well as
the Template Haskell changelog,
- - - - -
1884dd1a by Simon Peyton Jones at 2025-03-18T20:05:03-04:00
Add -Wrule-lhs-equalities warning
This commit adds a new warning, controlled by the warning flag,
-Wrule-lhs-equalities, which is emitted when the LHS of a RULE gives
rise to equality constraints that previous GHC versions would have
quantified over.
GHC instead discards such RULES, as GHC was never able to generate
a rule template that would ever fire; it's better to be explicit about
the fact that the RULE doesn't work.
- - - - -
b00b3ef0 by Ben Gamari at 2025-03-18T20:05:41-04:00
compiler: Add export list to GHC.SysTools.Process
This also revealed that `readProcessEnvWithExitCode` and its local
helpers were dead code.
- - - - -
25850b22 by ARATA Mizuki at 2025-03-18T20:06:25-04:00
Fix code generation for SSE vector operations
The new implementation generates correct code
even if the registers overlap.
Closes #25859
- - - - -
e576468c by Andreas Klebinger at 2025-03-18T20:07:02-04:00
Bump nofib submodule.
Fixes #25867. (Ben-raytrace being broken by library changes)
- - - - -
443fc8b1 by Sjoerd Visscher at 2025-03-19T12:01:04-04:00
Multiplicity annotation on records
Needing to store multiplicity annotations on records triggered a refactoring of AST of data declarations:
Moved HsBangTy and HsRecTy from HsType to HsTypeGhcPsExt, the extension of HsType during parsing, since they are only needed during parsing.
New HsConDeclField that stores all source data shared by all constructor declaration fields: unpackedness, strictness, multiplicity, documentation and the type of the field.
Merged HsMultAnn and HsArrowOf, so all multiplicity annotations share the same data type.
HsBang was no longer needed as a separate type, and was inlined into HsSrcBang.
- - - - -
313cf271 by Ben Gamari at 2025-03-19T12:01:43-04:00
gitlab-ci: Drop CentOS 7 binary distributions
CentOS 7 is EoL and moreover we cannot even build images for it.
See #25061.
- - - - -
5b94f99f by Ben Gamari at 2025-03-19T12:02:21-04:00
rts: Ensure that WinIO flag is set when --io-manager=auto
As noted in #25838, previously `selectIOManager` failed to set
`rts_IOManagerIsWin32Native` in its `IO_MNGR_FLAG_AUTO`. This meant
that the MIO path was taken when WinIO was supposedly selected,
resulting in chaos.
Fixes #25838.
- - - - -
1a3f1131 by Peng Fan at 2025-03-19T12:03:10-04:00
Pass the mcmodel=medium parameter to CC via GHC
Ensure that GHC-driver builds default to mcmodel=medium, so that GHC
passes this default parameter to CC without having to add it to the
compiled project.
Commit e70d41406b5d5638b42c4d8222cd03e76bbfeb86 does not ensure that all
GHC-built object files have a default model of medium, and will raise an
R_LARCH_B26 overflow error.
- - - - -
27cf7361 by Matthew Craven at 2025-03-19T12:03:48-04:00
Add interface-stability test for ghc-bignum
As with ghc-prim, it makes sense to have some protection against
accidental interface changes to this package caused by changes
in ghc-internal.
- - - - -
25d46547 by Matthew Craven at 2025-03-19T12:03:48-04:00
Add README reference for the interface-stability tests
- - - - -
5d65393e by Simon Peyton Jones at 2025-03-20T05:41:24-04:00
Remove the Core flattener
This big MR entirely removes the "flattener" that took a type and
replaced each type-family application with a fresh type variable.
The flattener had its origin in the paper
Injective type families for Haskell
But (a) #25657 showed that flattening doesn't really work.
(b) since we wrote the paper we have introduced the so-called
"fine-grained" unifier GHC.Core.Unify, which can return
* SurelyApart
* Unifiable subst
* MaybeApart subst
where the MaybeApart says that the two types are not unifiable by a
substitution, but could (perhaps) be unified "later" after some type
family reductions. This turns out to subsume flattening.
This MR does a major refactor of GHC.Core.Unify to make it capable of
subsuming flattening. The main payload is described in
Note [Apartness and type families]
and its many wrinkles.
The key (non-refactoring) implementation change is to add `um_fam_env`
to the `UMState` in the unification monad.
Careful review with Richard revealed various bugs in the treament of
`kco`, the kind coercion carried around by the unifier, so that is
substantially fixed too: see Note [Kind coercions in Unify].
Compile-time performance is improved by 0.1% with a few improvements over
1% and one worsening by 1.3% namely T9872a. (I have not investigated the
latter.)
Metric Decrease:
T9872b
T9872c
TcPlugin_RewritePerf
Metric Increase:
T9872a
- - - - -
9003ef0a by sheaf at 2025-03-20T05:42:08-04:00
Remove SDoc from UnknownSubordinate/MissingBinding
This commit replaces unstructured SDoc arguments in error message constructors
with uses of the following two datatypes:
- SigLike: for different kinds of signatures (e.g. standalone kind signatures,
fixity signatures, COMPLETE pragmas, etc)
- Subordinate: for class methods, associated types, and record fields
The following error message constructors now no longer have any SDocs in them:
- TcRnIllegalBuiltinSyntax: SDoc -> SigLike
- MissingBinding: SDoc -> SigLike
- UnknownSubordinate: SDoc -> (Name, Subordinate)
- SuggestMoveToDeclarationSite: SDoc -> SigLike
- - - - -
4329f3b6 by sheaf at 2025-03-20T05:42:08-04:00
Remove SDocs from HsDocContext
This commit removes the remaining SDocs from the HsDocContext data type.
It adds the following constructors:
ClassInstanceCtx -- Class instances
ClassMethodSigCtx -- Class method signatures
SpecialiseSigCtx -- SPECIALISE pragmas
PatSynSigCtx -- Pattern synonym signatures
We now report a bit more information for errors while renaming class instances,
which slightly improves renamer-emitted error messages.
- - - - -
75c29aa1 by sheaf at 2025-03-20T05:42:08-04:00
Reject instance with non-class head in renamer
This commit modifies rnClsInstDecl so that, when renaming, we reject a class
instance declaration in which the head is not a class. Before this change, it
would get rejected in the type-checker, but that meant that the renamer could
emit unhelpful error messages, e.g.:
data Foo m a
instance Foo m where
fmap _ x = case x of
would rather unhelpfully say:
‘fmap’ is not a (visible) method of class ‘Foo’
when of course 'Foo' is not even a class. We now reject the above program
with the following error message:
Illegal instance for data type ‘Foo’.
Instance heads must be of the form
C ty_1 ... ty_n
where ‘C’ is a class.
Fixes #22688
- - - - -
a8f543a9 by Cheng Shao at 2025-03-20T18:47:19-04:00
testsuite: mark T7919 as fragile on i386 as well
T7919 may also fail i386 CI jobs with test timeout.
- - - - -
256ac29c by sheaf at 2025-03-20T18:48:07-04:00
Don't cache solved [W] HasCallStack constraints
This commit ensures we do not add solved Wanted constraints that mention
HasCallStack or HasExceptionContext constraints to the set of solved
Wanted dictionary constraints: caching them is invalid, because re-using
such cached dictionaries means using an old call-stack instead of
constructing a new one, as was reported in #25529.
Fixes #25529.
- - - - -
47646ce2 by Andrew Lelechenko at 2025-03-20T18:48:43-04:00
Improve haddock-visible documentation for GHC.Driver.Flags
- - - - -
2e4e15ed by Sylvain Henry at 2025-03-21T17:49:36-04:00
Document -fnum-constant-folding (#25862)
- - - - -
044a6e08 by sheaf at 2025-03-21T17:50:24-04:00
LLVM: fix typo in padLiveArgs
This commit fixes a serious bug in the padLiveArgs function, which
was incorrectly computing too many padding registers. This caused
segfaults, e.g. in the UnboxedTuples test.
Fixes #25770
Fixes #25773
- - - - -
1745c749 by Teo Camarasu at 2025-03-22T18:42:37-04:00
template-haskell: remove Language.Haskell.TH.Lib.Internal
This module is purely used for the implementation of TH quote
desugarring.
Historically this needed to be exposed from `template-haskell`, since
that's the package that the desugarred expressions referenced but since
https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12479, this is no
longer the case.
Now these identifiers are in `ghc-internal`.
Note that this module has carried the following warning for a long time:
> This is not a part of the public API, and as such, there are no API guarantees for this
module from version to version.
Resolves #24766
- - - - -
3bc507db by Alan Zimmerman at 2025-03-22T18:43:13-04:00
EPA: Fix exact printing of SPECIALISE pragma
This commit fixes two minor issues with exactprinting of the
SPECIALISE pragma after !12319 landed
- The span for the RHS did not include the optional signature type
- The `::` was printed twice when the legacy path was used
Closes #25885
- - - - -
bdf93da8 by sheaf at 2025-03-24T11:25:12+01:00
Renamer: improve handling of export children
This commit refactors the 'childGREPriority' function which is used when
renaming subordinate items in export lists and class declarations.
Instead of having a complicated LookupChild parameter, we now simply pass the
GREInfo of the parent, which allows us to decide what is a valid child:
- classes can have children that are in the type constructor namespace,
- promoted data constructors should be treated the same as normal data
constructors.
Fixes #24027
- - - - -
1dbc7846 by Matthew Pickering at 2025-03-24T15:35:17-04:00
Revert "mk-ghcup-metadata: Clean up and add type annotations"
This reverts commit 64ea68d9a206ec4db5020b0a3fc563199ab18be3.
See #25889
- - - - -
6941c825 by doyougnu at 2025-03-25T10:05:58-04:00
base: construct compat RTSFlags
-- see CLC #289
- - - - -
730e6f77 by doyougnu at 2025-03-25T10:06:02-04:00
base: construct compat GHC.Stats
-- see CLC #289
- - - - -
cd9e6605 by Ben Gamari at 2025-03-25T17:59:52-04:00
rel_eng/upload: Clarify usage directions
Previously it was not made clear that the directory name is significant.
- - - - -
7d18c19b by Cheng Shao at 2025-03-25T22:00:56+00:00
ghci: make the Pipe type opaque
This commit makes the Pipe type in ghci opaque, and introduce the
mkPipeFromHandles constructor for creating a Pipe from a pair of
Handles. Pipe is now just a pair of receiver/sender continuations
under the hood. This allows a Pipe to be potentially backed by other
IPC mechanisms (e.g. WebSockets) which is essential for wasm ghci
browser mode.
- - - - -
a2103fd2 by Cheng Shao at 2025-03-25T22:00:56+00:00
ghci: use improved Pipe logic for wasm iserv
This commit makes wasm iserv take advantage of the Pipe refactoring by
passing binary receiver/sender js callbacks from the dyld script. This
paves the way for piping the binary messages through WebSockets in
order to run wasm iserv in the browser, but more importantly, it
allows us to get rid of a horrible hack in the dyld script: we no
longer have to fake magical wasi file descriptors that are backed by
nodejs blocking I/O! The legacy hack was due to these facts:
- iserv only supported exchanging binary messages via handles backed
by file descriptors
- In wasi you can't access host file descriptors passed by host ghc
- The nodejs wasi implementation only allows mapping host directories
into the wasi vfs, not host file descriptors
- Named pipes with file paths (mkfifo) doesn't work well with nodejs
wasi implementation, causes spurious testsuite failures on macos
But starting from this point, we can fully take advantage of
non-blocking I/O on the js side.
- - - - -
fa2fbd2b by Cheng Shao at 2025-03-25T22:00:56+00:00
ghci: fix ^C handling for wasm iserv
This commit fixes ^C handling for wasm iserv. Previously we didn't
handle it at all, so ^C would kill the node process and host ghc would
then crash as well. But native ghc with external interpreter can
handle ^C just fine and wasm should be no different. Hence the fix:
wasm iserv exports its signal handler as a js callback to be handled
by the dyld script. Also see added note for details.
- - - - -
efcebed6 by Cheng Shao at 2025-03-25T22:00:56+00:00
wasm: fix post-link.mjs for browser
The wasm ghci browser mode needs to run dyld.mjs in the browser which
imports post-link.mjs. This script makes post-link.mjs runnable in the
browser by deferring node-specific module imports to their actual use
sites.
- - - - -
27bb73c6 by Cheng Shao at 2025-03-25T22:00:56+00:00
wasm: use console.assert in dyld script
This commit uses console.assert() instead of node-specific strict
assert in the dyld script, in order to make it runnable in the
browser. console.assert() only warns and doesn't crash upon assertion
failure, but this is fine; we can always trivially define a strict
assert function shall it be necessary when debugging, and there hasn't
been such an assertion failure seen in the wild for long enough.
- - - - -
929df0ba by Cheng Shao at 2025-03-25T22:00:56+00:00
wasm: asyncify the dylink.0 custom section parser
This commit refactors the simple binary parser in the dyld script in
charge of parsing the dylink.0 custom section. Previously the parser
was synchronous and operated on the entire input buffer; this was
simple and easy and worked well enough when the input wasm modules are
instantly read from local filesystem.
However, when running dyld in the browser, the wasm modules are
transferred via fetch() requests. The host ghc and the browser might
not be on the same machine, so slow network uplink does need to be
considered. We only need to parse dylink.0 custom section to extract
dependency info, and dylink.0 is the very first custom section in the
wasm shared library binary payload, so the parsing process should not
require fetch() to complete and should return the parsing result asap.
Hence the refactorings in this commit: asyncify the parser, make it
only consume as many bytes as needed by invoking an async consumer
callback. The input is a readable stream from the fetch() response;
once the response is available, the async wasm compilation can start
in the background, and dylink.0 parsing shall end asap which results
in more wasm shared libraries to be loaded earlier. Profit.
- - - - -
9a697181 by Cheng Shao at 2025-03-25T22:00:56+00:00
wasm: fix dyld setImmediate usage in browser
The wasm dyld script used to only run in node and directly uses
setImmediate in globalThis. In case of browsers, it needs to import
setImmediate from the prelude, hence this commit.
- - - - -
d9b71e82 by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: fix dyld downsweep filepath handling in browser
The wasm dyld downsweep logic used to rely on nodejs path module to
handle filepaths. That's not available in browsers, so this commit
implements poor man's filepath handling in js, which is not elegant
for sure but works for both nodejs and the browser.
- - - - -
7003a399 by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: isolate nodejs-specific logic with the isNode flag in dyld
As we move towards supporting running the dyld script in the browser,
this commit implements the isNode module-level binding which is true
if dyld is running in nodejs. The nodejs-specific bits are gated under
isNode.
For the browser case, this commit introduces @bjorn3/browser_wasi_shim
as the wasi implementation; we already use it in quite a few projects
and it simply works.
- - - - -
22ba2a78 by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: isolate dyld side effects that might require IPC
This commit spins out a DyLDHost class from DyLD that handles side
effects that must be run in the same host environment that runs
wasm32-wasi-ghc. When the dyld script runs in the browser, it'll need
to do IPC to find libraries, fetch wasm library, etc, and the other
side of dyld that runs on nodejs would simply expose the DyLDHost
methods as endpoints for WebSockets/HTTP.
- - - - -
e93fc33d by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: implement wasm ghci browser mode
This commit implements the rest of dyld logic that delivers the ghci
browser mode:
- The dyld script can now fully run in the browser. It communicates
back with dyld-on-nodejs via WebSockets and also plain HTTP 1.1
requests.
- The host dyld starts a server and acts as a broker between the GHC
process and the browser side. GHC doesn't need to know anything
about the browser mode; no driver flags need to be added and no
recompilation needs to happen, the GHC driver continues to use the
original iserv binary messages protocol.
- The dyld broker doesn't need to parse any message between the
browser dyld and GHC; it merely sets up WebSockets connections to
redirect these messages as well as ^C signals.
- Plain HTTP 1.1 is used for IPC requests (e.g. downloading a wasm
module).
- The dyld broker serves a main.js script that bootstraps iserv in the
browser, and a main.html empty page playground for testing. CORS is
enabled so it could be possible to inject iserv into other websites
and use ghci to play with them.
- All the RPC logic is opaque to the DyLD class, the majority of the
wasm dynamic linker code is already portable and runs fine in
firefox/chrome/webkit.
Closes #25399.
- - - - -
fc576798 by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: add puppeteer/playwright support for ghci browser mode
This commit adds support for using puppeteer/playwright for
automatically launching a headless browser that backs the ghci browser
mode. This is useful for testing the ghci browser mode as a part of
GHC testsuite, and it's also convenient for local development since
the step to start iserv can be automated away.
- - - - -
ad7e271d by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: support wasi console redirect for the ghci browser mode
This commit adds optional support for redirecting wasi console
stdout/stderr back to the host when running wasm ghci browser mode. By
default, the wasi console outputs are only available under F12
devtools console, but in case of testing against a mobile browser, the
devtools console may not be readily available, and it would be more
convenient to at least get wasi console output on the host side.
The redirection logic is simple, just adding another two WebSockets
connections that pump the line-buffered textual messages back to
host.
- - - - -
731217ce by Cheng Shao at 2025-03-25T22:00:57+00:00
wasm: add brotli compression for ghci browser mode
This commit adds brotli compression for wasm shared libraries for ghci
browser mode. With BROTLI_MIN_QUALITY, the overhead is negligible, and
it helps reducing amount of transferred data when the browser connects
to the server over a slow connection.
- - - - -
ac70e643 by Cheng Shao at 2025-03-26T13:37:19+00:00
testsuite: add browser001 test for wasm ghci browser mode
This commit adds support for testing the wasm ghci browser mode in the
testsuite, as well as a simple first test case browser001 that makes
use of TH, JSFFI and browser-specific DOM API. See added note and
comments for details.
- - - - -
6ef5c0d2 by Cheng Shao at 2025-03-26T13:37:24+00:00
docs: add wasm ghci subsection in user manual
This commit updates the user manual to add wasm ghci subsection.
- - - - -
37381bcf by Cheng Shao at 2025-03-26T13:37:24+00:00
docs: update Note [The Wasm Dynamic Linker]
This commit updates Note [The Wasm Dynamic Linker] to reflect recent
developments, in particular the wasm ghci browser mode.
- - - - -
4b5a0f61 by Cheng Shao at 2025-03-26T13:37:24+00:00
ci: bump DOCKER_REV and test wasm ghci browser mode
This commit bumps the ci-images revision for updated wasm toolchain,
and adds the launch options required to test wasm ghci browser mode.
- - - - -
c6a3bc8f by Cheng Shao at 2025-03-26T13:37:24+00:00
driver: implement wasm ghci browser mode flags
This commit implements GHC driver flags that enable the wasm ghci
browser mode.
- - - - -
f75e823e by Cheng Shao at 2025-03-26T18:01:54-04:00
rts: add hs_try_putmvar_with_value to RTS API
This commit adds hs_try_putmvar_with_value to rts. It allows more
flexibility than hs_try_putmvar by taking an additional value argument
as a closure to be put into the MVar. This function is used & tested
by the wasm backend runtime, though it makes sense to expose it as a
public facing RTS API function as well.
- - - - -
9cd9f347 by Cheng Shao at 2025-03-26T18:01:54-04:00
wasm: use MVar as JSFFI import blocking mechanism
Previously, when blocking on a JSFFI import, we push a custom
stg_jsffi_block stack frame and arrange the `promise.then` callback to
write to that stack frame. It turns out we can simply use the good old
MVar to implement the blocking logic, with a few benefits:
- Less maintenance burden. We can drop the stg_jsffi_block related Cmm
code without loss of functionality.
- It interacts better with existing async exception mechanism. throwTo
would properly block the caller if the target thread is masking
async exceptions.
- - - - -
da34f0aa by Cheng Shao at 2025-03-26T18:01:54-04:00
wasm: properly pin the raiseJSException closure
We used to use keepAlive# to pin the raiseJSException closure when
blocking on a JSFFI import thunk, since it can potentially be used by
RTS. But raiseJSException may be used in other places as well (e.g.
the promise.throwTo logic), and it's better to simply unconditionally
pin it in the JSFFI initialization logic.
- - - - -
dc904bfd by Cheng Shao at 2025-03-26T18:01:54-04:00
wasm: implement promise.throwTo() for async JSFFI exports
This commit implements promise.throwTo() for wasm backend JSFFI
exports. This allows the JavaScript side to interrupt Haskell
computation by raising an async exception. See subsequent docs/test
commits for more details.
- - - - -
7f80455e by Cheng Shao at 2025-03-26T18:01:55-04:00
testsuite: add test for wasm promise.throwTo() logic
This commit adds a test case to test the wasm backend
promise.throwTo() logic.
- - - - -
afdd3fe7 by Cheng Shao at 2025-03-26T18:01:55-04:00
docs: document the wasm backend promise.throwTo() feature
- - - - -
65dc65dc by sheaf at 2025-03-26T18:02:43-04:00
Refactor CtEvidence into Given/Wanted
This commit is a simple refactoring which splits up the CtEvidence,
giving each constructor its own datatype:
data CtEvidence
= CtGiven GivenCtEvidence
| CtWanted WantedCtEvidence
data GivenCtEvidence =
GivenCt
{ ctev_pred :: TcPredType
, ctev_evar :: EvVar
, ctev_loc :: CtLoc }
data WantedCtEvidence =
WantedCt
{ ctev_pred :: TcPredType
, ctev_dest :: TcEvDest
, ctev_loc :: CtLoc
, ctev_rewriters :: RewriterSet }
This enables a few minor simplifications in the code, notably removing
a panic from GHC.Tc.Solver.Solve.solveWantedForAll_implic.
Fixes #25848
- - - - -
ada04031 by sheaf at 2025-03-26T18:03:27-04:00
Export lists: same prio for NoParent & RightParent
This commit ensures that, when we are renaming children in an export
list item such as
module M ( P(A,B,C) )
we consider children with NoParent to have the same priority as children
which have the correct parent (P in this case). This is because we
should **not** prioritise a data constructor (with the right parent)
over a pattern synonym we are bundling (which, before bundling, has
no parent).
Fixes #25892
- - - - -
721628a0 by Adriaan Leijnse at 2025-03-27T09:10:10-04:00
TTG: Replace HsUnboundVar with HsHole
Context:
The HsUnboundVar constructor in Language.Haskell.Syntax.Expr contained a
RdrName, which stood in the way of the work towards a dedicated
haskell-syntax library. The constructor was overloaded for unbound
variables, anonymous and named holes, and parse errors.
This commit:
Replaces HsUnboundVar with HsHole. In the surface syntax HsHole only
represents an anonymous expression hole ("_"). It is extended with the
XHole type family.
In the concrete GHC implementation of the language on the other hand,
HsHole is used for "any thing which is not necessarily a valid or fully
defined program fragment, but for which a type can be derived". This use
is similar to how HsUnboundVar was used, but the parse error case is now
made explicit with a ParseError case for XHole. This is in anticipation
of future work on a fault tolerant compilation pipeline.
- - - - -
dbd852f5 by Ben Gamari at 2025-03-27T09:10:48-04:00
rel_eng: Finish removal of CentOS jobs
Remove centos7 from release fetch and ghcup metadata generation scripts.
Closes #25893.
- - - - -
0e0231e7 by Matthew Pickering at 2025-03-28T18:36:33-04:00
hadrian: Make hash_unit_ids into a flavour transformer (and enable for release flavour)
The primary reason for this change is to make the `release` flavour
enable `--hash-unit-ids` by default without any further user intervention.
* Packagers don't have to be aware of this special flag they should be
using.
* release builds on CI are uniformly testing with hashes (see !13418)
Fixes #25379
- - - - -
9fc54c12 by Rodrigo Mesquita at 2025-03-28T18:37:10-04:00
driver: Move DynFlags consistency fixes off Main
These consistency fixes found in Main.hs are required for the proper
functioning of the compiler and should live together with all remaining
fixes in `makeDynFlagsConsistent`.
This is especially relevant to GHC applications that shouldn't have to
copy/fix themselves possibly inconsistent DynFlags.
Additionally, outputs information when verbosity is high about these
consistency fixes that were previously quiet, adds information to the
Note on consistency of DynFlags, and improves one of the fixes that
incorrectly used `dynNow`.
- - - - -
2fdd0be9 by sheaf at 2025-03-28T18:37:53-04:00
Remove GhcHint from TcRnNotInScope constructor
This is a tiny refactoring which:
- removes GhcHint/ImportError fields from some constructors of
TcRnMessage, using the TcRnMessageDetailed mechanism instead to
report this informaiton:
- removes the GhcHint and ImportErrors fields from TcRnNotInScope
- removes the GhcHint field from TcRnTermNameInType
- ensures that we only include these hints and import errors when the
-fhelpful-errors flag is turned on
Fixes #25874
- - - - -
9e5cd064 by ARATA Mizuki at 2025-03-31T14:53:34-04:00
Better support for SSE3 and SSE4.1
In particular:
* Pass appropriate attributes to LLVM
* Define preprocessor macros for them
- - - - -
c2c7dd51 by ARATA Mizuki at 2025-03-31T14:53:34-04:00
x86: Add support for SSSE3
This commit adds the `-mssse3` flag, which controls usage of SSSE3 instructions in x86 code generation.
- - - - -
d7c62580 by ARATA Mizuki at 2025-03-31T14:53:34-04:00
x86 NCG SIMD: Implement 128-bit integer vector arithmetics
This commit implements the following operations on integer vectors:
* negateIntNXM#
* plus{Int,Word}NXM#
* minus{Int,Word}NXM#
* times{Int,Word}NXM#
* quot{Int,Word}NXM#
* rem{Int,Word}NXM#
* min{Int,Word}NXM#
* max{Int,Word}NXM#
where (N,M) is one of (8,16), (16,8), (32,4), or (64,2).
Closes #25643
- - - - -
f5ea4e7e by ARATA Mizuki at 2025-03-31T14:53:34-04:00
x86 NCG SIMD: Implement 128-bit integer vector shuffle
This commit implements the following operations:
* shuffle{Int,Word}8X16#
* shuffle{Int,Word}16X8#
* shuffle{Int,Word}32X4#
* shuffle{Int,Word}64X2#
See #25643
- - - - -
5eeb6645 by Simon Peyton Jones at 2025-03-31T14:54:16-04:00
Re-jig the way that the Simplifier tries RULES
As #25170 showed, if a new RULE appears, it could change the simplifier's
behaviour a bit, even if it never fires; and that messes up deterministic
compilation. (This was particularly nasty if the rule wasn't even transitively
below the module being compiled.)
This MR rejigs the use of `tryRules` so that behaviour does not change
when a new, unrelated RULE is added. It's described in
* Note [When to apply rewrite rules]
* Note [tryRules: plan (BEFORE)]
* Note [tryRules: plan (AFTER)]
The main change is in the refactored version of
* simplOutId
* rebuildCall
The little state machine that was embedded in ArgInfo is gone.
As I wandered around the Simplifier I also found opportunities for
some loosely-related refactoring:
* In several places, the /substitution/ in the SimpleEnv is empty;
all we care about is the in-scope set and the flags. So
- I made a synonym `SimplEnvIS` that embodies that invariant,
- used it in a number of type signatures (notably `rebuild`)
- added some assertion checks (via `checkSimlEnvIS`)
* I moved the hanlding of `runRW` out of `rebuildCall` (where we
would have to test repeatedly) and into the new `simplOutId`, which
fires up `rebuildCall`. Now it is only tested once.
-------------------------
Metric Decrease:
T9020
T9961
-------------------------
- - - - -
f534474a by sheaf at 2025-03-31T14:54:59-04:00
Add comment: no qualified Names in the LocalRdrEnv
This commit adds a reference to section 5.5.1 of the Haskell 2010 report,
to explain that qualified names can't occur in the LocalRdrEnv.
Fixes #25875
- - - - -
d5ea80c6 by Patrick at 2025-03-31T14:55:42-04:00
Fix deadlock/loop in interface rehydration (#25858)
In #25858, GHC hangs when processing modules with class defaults due to a
circular dependency in the interface rehydration process. The deadlock/loop
occurred when eager class defaults rehydration accessed not-yet-complete module details.
To fix the immediate deadlock/loop.
`tcIfaceDefaults` is refactored, we use the class name directly from the iface
and use `forM` for lazy loading the class, which algins with the handling of other fields
of ModDetails. This laziness ensure rehydration waits for HomePackageTable (HPT) to
be updated and prevent premature evaluation of ModDetails inside `fixIO``.
As suggested by Matthew, class defaults importing is also refactored
to align with the compiler's established interface loading conventions.
- add class defaults field to ExternalPackageState (EPS).
- rehydrate and store class defaults in EPS at `loadInterface`.
- Instead of using `tcIfaceDefaults` in `tcRnImports`, we add and use
`tcGetClsDefaults` to read defaults directly from HPT or EPS
when importing modules.
Tests:
- T25858, T25858v1-2: Test class hydration in defaults
- T25858v3-4: Test type list hydration in defaults
New Note [Tricky rehydrating IfaceDefaults loop] is added.
Thanks to @sheaf (Sam), @mpickering (Matthew), and @simonpj (Simon) for their
valuable input and analysis.
Fixes #25858.
- - - - -
2d419d8d by Matthew Pickering at 2025-04-02T16:12:36-04:00
Use unsafePerformIO in definition of computeFingerprint
computeFingerprint is morally a pure function, which is implemented by
mutating a buffer. Using unsafePerformIO inside the definition allows it
to be used in pure contexts, fixing one place where an ad-hoc call to
unsafePerformIO is already needed.
- - - - -
ccdf979b by Matthew Pickering at 2025-04-02T16:12:37-04:00
driver: Fix recompilation checking for exported defaults
Since the exported defaults are not associated with any identifier from
the module, they are just added to the export hash rather than
the fine-grained recompilation logic.
Fixes #25855
- - - - -
c5bf9892 by Matthew Pickering at 2025-04-02T16:12:37-04:00
driver: Fix recompilation checking for COMPLETE pragmas
A {-# COMPLETE P, Q #-} pragma is associated with the pattern synonyms P
and Q during recompilation checking. Therefore, the existence of a
pattern synonym becomes part of the ABI hash for P and Q.
Then if a module uses these pattern synonyms and a complete pragma
changes, it will trigger recompilation in that module.
Fixes #25854
- - - - -
d0fd9370 by sheaf at 2025-04-02T16:14:05-04:00
Handle named default exports separately
This commit changes the way we check for duplicate exports of named
default declarations. They are now treated entirely separately from
other exports, because in an export list of the form
module M ( default Cls, Cls )
the default declaration does not export the class 'Cls', but only its
default declarations.
Also fixes a bug in Backpack where named default exports were getting
dropped entirely. No test for that.
Fixes #25857
- - - - -
62d04494 by Cheng Shao at 2025-04-03T05:56:17-04:00
ci: add x86_64-linux-ubuntu24_04 nightly/release jobs
- - - - -
327952e4 by Cheng Shao at 2025-04-03T05:56:17-04:00
rel-eng: add ubuntu24_04 bindists to ghcup metadata and fetch gitlab scripts
- - - - -
aa1e3b8b by sheaf at 2025-04-03T05:57:24-04:00
GHC settings: always unescape escaped spaces
In #25204, it was noted that GHC didn't properly deal with having
spaces in its executable path, as it would compute an invalid path
for the C compiler.
The original fix in 31bf85ee49fe2ca0b17eaee0774e395f017a9373 used a
trick: escape spaces before splitting up flags into a list. This fixed
the behaviour with extra flags (e.g. -I), but forgot to also unescape
for non-flags, e.g. for an executable path (such as the C compiler).
This commit rectifies this oversight by consistently unescaping the
spaces that were introduced in order to split up argument lists.
Fixes #25204
- - - - -
34a9b55d by lazyLambda at 2025-04-04T06:22:26-04:00
Driver: make MonadComprehensions imply ParallelListComp
This commit changes GHC.Driver.Flags.impliedXFlags to make the
MonadComprehensions extension enable the ParallelListComp extension.
Fixes #25645
- - - - -
d99eb7cd by sheaf at 2025-04-04T06:23:28-04:00
NamedDefaults: handle poly-kinded unary classes
With this commit, we accept named default declarations for poly-kinded
classes such as Typeable, e.g.
default Typeable (Char)
This used to fail because we assumed the kind of the class was monomorphic,
e.g.
Type -> Constraint
(Type -> Type) -> Constraint
Nat -> Constraint
Now, we can handle a simple polymorphic class such as
Typeable :: forall k. k -> Constraint
Note that we keep the restriction that the class must only have
one visible argument.
This is all explained in the new Note [Instance check for default declarations]
in GHC.Tc.Gen.Default.
Fixes #25882
- - - - -
4cbc90de by sheaf at 2025-04-04T11:39:05-04:00
LLVM: add type annotations to AtomicFetch_cmm.cmm
- - - - -
e2237305 by sheaf at 2025-04-04T11:39:05-04:00
Cmm lint: lint argument types of CallishMachOps
This commit adds a new check to Cmm lint to ensure that the argument
types to a CallishMachOp are correct. The lack of this check was
detected in the AtomicFetch test: the literals being passed as the
second arguments to operations such as 'fetch_add', 'fetch_and'... were
of the wrong width, which tripped up the LLVM backend.
- - - - -
9363e547 by Cheng Shao at 2025-04-04T11:39:50-04:00
ci: add ghc-wasm-meta integration testing jobs
This patch adds ghc-wasm-meta integration testing jobs to the CI
pipeline, which are only triggered via the `test-wasm` MR label or
manually when the `wasm` label is set.
These jobs will fetch the wasm bindists and test them against a
variety of downstream projects, similarly to head.hackage jobs for
native bindists, offering a convenient way to catch potential
downstream breakage while refactoring the wasm backend.
- - - - -
27029e60 by Adam Gundry at 2025-04-04T11:40:36-04:00
base: Minor fixes to GHC.Records haddocks
This corrects a stale reference to OverloadedRecordFields (which should
be OverloadedRecordDot), fixes the haddock link syntax and adds an
@since pragma.
- - - - -
f827c4c6 by Rodrigo Mesquita at 2025-04-07T11:22:10-04:00
Parametrize default logger action with Handles
Introduce `defaultLogActionWithHandles` to allow GHC applications to use
GHC's formatting but using custom handles.
`defaultLogAction` is then trivially reimplemented as
```
defaultLogActionWithHandles stdout stderr
```
- - - - -
5dade5fd by sheaf at 2025-04-07T11:23:02-04:00
Finer-grained recompilation checking for exports
This commit refines the recompilation checking logic, to avoid
recompiling modules with an explicit import list when the modules they
import start exporting new items.
More specifically, when:
1. module N imports module M,
2. M is changed, but in a way that:
a. preserves the exports that N imports
b. does not introduce anything that forces recompilation downstream,
such as orphan instances
then we no longer require recompilation of N.
Note that there is more to (2a) as initially meets the eye:
- if N includes a whole module or "import hiding" import of M,
then we require that the export list of M does not change,
- if N only includes explicit imports, we check that the imported
items don't change, e.g.
- if we have @import M(T(K, f), g)@, we must check that N
continues to export all these identifiers, with the same Avail
structure (i.e. we should error if N stops bundling K or f with
T)
- if we have @import M(T(..))@, we must check that the children
of T have not changed
See Note [When to recompile when export lists change?] in GHC.Iface.Recomp.
This is all tested in the new tests RecompExports{1,2,3,4,5}
Fixes #25881
- - - - -
f32d6c2b by Andreas Klebinger at 2025-04-07T22:01:25-04:00
NCG: AArch64 - Add -finter-module-far-jumps.
When enabled the arm backend will assume jumps to targets outside of the
current module are further than 128MB away.
This will allow for code to work if:
* The current module results in less than 128MB of code.
* The whole program is loaded within a 4GB memory region.
We have seen a few reports of broken linkers (#24648) where this flag might allow
a program to compile/run successfully at a very small performance cost.
-------------------------
Metric Increase:
T783
-------------------------
- - - - -
553c280b by Andreas Klebinger at 2025-04-07T22:02:11-04:00
Revert "rts: fix small argument passing on big-endian arch (fix #23387)"
Based on analysis documented in #25791 this doesn't fully fix the big
while introducing new bugs on little endian architectures.
A more complete fix will have to be implemented to fix #23387
This reverts commit 4f02d3c1a7b707e609bb3aea1dc6324fa19a5c39.
- - - - -
b0dc6599 by Andreas Klebinger at 2025-04-07T22:02:11-04:00
Interpreter: Fixes to handling of subword value reads/writes.
Load subword values as full words from the stack truncating/expanding as
neccesary when dealing with subwords. This way byte order is implicitly
correct.
This commit also fixes the order in which we are pushing literals onto
the stack on big endian archs.
Last but not least we enable a test for ghci which actually tests these
subword operations.
- - - - -
ed38c09b by Cheng Shao at 2025-04-07T22:02:53-04:00
testsuite: don't test WasmControlFlow stdout
This patch solves a potential test flakiness in `WasmControlFlow` by
removing `WasmControlFlow.stdout` which is not so portable/stable as
it seems. See added `Note [WasmControlFlow]` for more detailed
explanation.
- - - - -
f807c590 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: Add docs to obtainTermFromId
- - - - -
5dba052d by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
Move logic to find and set Breakpoint to GHC
Breakpoints are uniquely identified by a module and an index unique
within that module. `ModBreaks` of a Module contains arrays mapping from
this unique breakpoint index to information about each breakpoint. For
instance, `modBreaks_locs` stores the `SrcSpan` for each breakpoint.
To find a breakpoint using the line number you need to go through all
breakpoints in the array for a given module and look at the line and
column stored in the `SrcSpan`s. Similarly for columns and finding
breakpoints by name.
This logic previously lived within the `GHCi` application sources,
however, it is common to any GHC applications wanting to set
breakpoints, like the upcoming `ghc-debugger`.
This commit moves this logic for finding and setting breakpoints to the
GHC library so it can be used by both `ghci` and `ghc-debugger`.
- - - - -
bc0b9f73 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
Refactor and move logic for identifier breakpoints
Breakpoints can be set on functions using syntax of the form
`[Module.]function`. The parsing, resolution (e.g. inferring implicit
module), and validation of this syntax for referring to functions was
tightly coupled with its GHCi use.
This commit extracts the general purpose bits of resolving this syntax
into `GHC.Runtime.Debugger.Breakpoints` so it can be further used by
other GHC applications and to improve the code structure of GHCi.
Moreover, a few utilities that do splitting and joining of identifiers
as strings were moved to `GHC.Runtime.Eval.Utils`, which also can be
used in the future to clean up `GHC.Runtime.Eval` a bit.
- - - - -
4f728d21 by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: derive Ord for BreakpointIds
- - - - -
5528771c by Rodrigo Mesquita at 2025-04-08T17:41:51-04:00
debugger: Move context utils from GHCi to GHC
Moves `enclosingTickSpan`, `getCurrentBreakSpan`, and
`getCurrentBreakModule`, general utilities on the internal debugger
state, into the GHC library.
- - - - -
4871f543 by sheaf at 2025-04-08T17:42:43-04:00
Implicit quantification in type synonyms: add test
This adds a test for ticket #24090, which involves implicit
quantification in type synonyms.
The underlying issue was fixed in 0d4ee209dfe53e5074d786487f531dabc36d561c.
- - - - -
48917d3c by sheaf at 2025-04-08T17:42:44-04:00
Turn on implicit-rhs-quantification by default
This flag was added to GHC 9.8, and will be removed in a future GHC
release. In preparation, this commit adds it to the default warning
flags.
- - - - -
629be068 by Rodrigo Mesquita at 2025-04-08T17:43:26-04:00
debugger: Add breakpoints to every Stmt
While single-stepping through a Haskell program we stop at every
breakpoint. However, we don't introduce breakpoints at every single
expression (e.g. single variables) because they would be too many and
uninteresting.
That said, in a do-block, it is expected that stepping over would break
at every line, even if it isn't particularly interesting (e.g. a single
arg like getArgs). Moreover, let-statements in do-blocks, despite only
being evaluated once needed, lead to surprising jumps while stepping
through because some have outermost (outside the let) breakpoints
while others don't.
This commit makes every statement in a do-block have a breakpoint.
This leads to predictable stepping through in a do-block.
Duplicate breakpoints in the same location are avoided using the
existing blacklist mechanism, which was missing a check in one relevant place.
Fixes #25932
- - - - -
99a3affd by Matthew Pickering at 2025-04-08T17:44:08-04:00
driver: refactor: Split downsweep and MakeAction into separate modules.
This will facilitate using the downsweep functions in other parts of
the compiler than just --make mode.
Also, the GHC.Driver.Make module was huge. Now it's still huge but
slightly smaller!
- - - - -
ecfec4df by sheaf at 2025-04-09T14:13:12-04:00
Store user-written qualification in the GhcRn AST
This commit ensures we store the original user-written module
qualification in the renamed AST. This allows us to take into account
the user-written qualification in error messages.
Fixes #25877
- - - - -
97c884e2 by sheaf at 2025-04-09T14:13:12-04:00
TcRnIllegalTermLevelUse: simpler error when possible
This commit makes GHC emit a simple error message in the case of an
illegal term-level use of a data constructor: we will try to report an
out-of-scope error instead of a "Illegal term level use" error, as the
latter might be a bit overwhelming for newcomers.
We do this when we have a data constructor import suggestion to provide
to the user. For example:
module M where { data A = A }
module N where
import M(A)
x = Bool
-- Illegal term-level use of Bool
y = A
-- Data constructor not in scope: A.
-- Perhaps add 'A' to the import list of 'M'.
This commit also revamps the "similar names" suggestion mechanism,
and in particular its treatment of name spaces. Now, which name spaces
we suggest is based solely on what we are looking for, and no longer on
the NameSpace of the Name we have. This is because, for illegal term-level
use errors, it doesn't make much sense to change the suggestions based
on the fact that we resolved to e.g. a type constructor/class; what
matters is what we were expecting to see in this position.
See GHC.Rename.Unbound.{suggestionIsRelevant,relevantNameSpace} as well
as the new constructors to GHC.Tc.Errors.Types.WhatLooking.
Fixes #23982
- - - - -
bff645ab by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00
driver: Split Session functions out of Main
This commit moves out functions that help in creating and validating a
GHC multi session from Main into the ghc library where they can be used by
other GHC applications.
Moreover, `Mode` processing and `checkOptions` linting were moved to
separate modules within the ghc-bin executable package.
In particular:
- Move `Mode` types and functions (referring to the mode GHC is running
on) to `ghc-bin:GHC.Driver.Session.Mode`
- Move `checkOptions` and aux functions, which validates GHC DynFlags
based on the mode, to `ghc-bin:GHC.Driver.Session.Lint`
- Moves `initMulti`, `initMake`, and aux functions, which initializes a make/multi-unit
session, into `ghc:GHC.Driver.Session.Units`.
- - - - -
501b015e by Rodrigo Mesquita at 2025-04-09T14:13:57-04:00
docs: Improve haddock of ExecComplete
- - - - -
dea98988 by Andreas Klebinger at 2025-04-09T19:23:57-04:00
Avoid oversaturing constructor workers.
Constructor applications always need to take the exact number of
arguments. If we can't ensure that instead apply the constructor worker
like a regular function.
Fixes #23865
- - - - -
f1acdd2c by sheaf at 2025-04-09T19:25:41-04:00
NamedDefaults: require the class to be standard
We now only default type variables if they only appear in constraints
of the form `C v`, where `C` is either a standard class or a class with
an in-scope default declaration.
This rectifies an oversight in the original implementation of the
NamedDefault extensions that was remarked in #25775; that implementation
allowed type variables to appear in unary constraints which had arbitrary
classes at the head.
See the rewritten Note [How type-class constraints are defaulted] for
details of the implementation.
Fixes #25775
Fixes #25778
- - - - -
5712e0d6 by Vladislav Zavialov at 2025-04-10T05:17:38+00:00
Retry type/class declarations and instances (#12088)
Retry type/class declarations and instances to account for non-lexical
dependencies arising from type/data family instances.
This patch improves the kind checker's ability to use type instances in kind
checking of other declarations in the same module.
* Key change: tcTyAndClassDecls now does multiple passes over the TyClGroups,
as long as it is able to make progress.
See the new Note [Retrying TyClGroups] in GHC.Tc.TyCl
* Supporting change: FVs of a TyClGroup are now recorded in its extension
field, namely XCTyClGroup.
See the new Note [Prepare TyClGroup FVs] in GHC.Rename.Module
* Instances are no longer inserted at the earliest positions where their FVs
are bound. This is a simplification.
See the new Note [Put instances at the end] in GHC.Rename.Module
* Automatic unpacking is now more predictable, but fewer fields get unpacked
by default. Use explicit {-# UNPACK #-} pragmas instead.
See the new Note [Flaky -funbox-strict-fields with type/data families]
For the wide range of newly accepted programs, consult the added test cases.
Fixed tickets:
#12088, #12239, #14668, #15561, #16410, #16448, #16693,
#19611, #20875, #21172, #22257, #25238, #25834
Metric Decrease:
T8095
- - - - -
bc73a78d by sheaf at 2025-04-10T15:07:24-04:00
checkFamApp: don't be so eager to cycle break
As remarked in #25933, a pure refactoring of checkTyEqRhs in
ab77fc8c7adebd610aa0bd99d653f9a6cc78a374 inadvertently changed behaviour,
as it caused GHC to introduce cycle-breaker variables in some
unnecessary circumstances.
This commit refactors 'GHC.Tc.Utils.Unify.checkFamApp' in a way that
should restore the old behaviour, so that, when possible, we first
recur into the arguments and only introduce a cycle breaker if this
recursion fails (e.g. due to an occurs check failure).
Fixes #25933
- - - - -
3acd8182 by Andreas Klebinger at 2025-04-10T22:32:12-04:00
Expand docs for RTS flag `-M`.
The behaviour of how/when exceptions are raised was not really covered
in the docs.
- - - - -
026c1a39 by Adam Sandberg Ericsson at 2025-04-10T22:32:56-04:00
add cases for more SchedulerStatus codes in rts_checkSchedStatus
- - - - -
5977c6a1 by sheaf at 2025-04-10T22:33:46-04:00
Squash warnings in GHC.Runtime.Heap.Inspect
There were incomplete record selector warnings in GHC.Runtime.Heap.Inspect
due to the use of the partial 'dataArgs' record selector. This is fixed
by passing the fields to the 'extractSubTerms' function directly,
rather than passing a value of the parent data type.
- - - - -
07a15e2a by Sven Tennie at 2025-04-11T18:47:16+02:00
RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738)
J_TBL result in local jumps, there should not deallocate stack slots
(see Note [extra spill slots].)
J is for non-local jumps, these may need to deallocate stack slots.
- - - - -
805 changed files:
- .gitlab-ci.yml
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/jobs.yaml
- .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py
- .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py
- .gitlab/rel_eng/upload.sh
- compiler/GHC.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/Cmm/CallConv.hs
- compiler/GHC/Cmm/Dataflow/Label.hs
- compiler/GHC/Cmm/Lint.hs
- compiler/GHC/Cmm/Liveness.hs
- compiler/GHC/Cmm/MachOp.hs
- compiler/GHC/Cmm/ThreadSanitizer.hs
- compiler/GHC/Cmm/Type.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/Config.hs
- compiler/GHC/CmmToAsm/PPC/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Linear/Base.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToAsm/X86/Instr.hs
- compiler/GHC/CmmToAsm/X86/Ppr.hs
- compiler/GHC/CmmToAsm/X86/RegInfo.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/CodeGen.hs
- compiler/GHC/Core.hs
- compiler/GHC/Core/Coercion/Axiom.hs
- compiler/GHC/Core/Coercion/Opt.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/FamInstEnv.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/LateCC/TopLevelBinds.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Map/Expr.hs
- compiler/GHC/Core/Map/Type.hs
- compiler/GHC/Core/Opt/CSE.hs
- compiler/GHC/Core/Opt/CallerCC/Types.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/SetLevels.hs
- compiler/GHC/Core/Opt/Simplify/Env.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Simplify/Utils.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Rules/Config.hs
- compiler/GHC/Core/SimpleOpt.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/Core/TyCo/Compare.hs
- compiler/GHC/Core/TyCo/FVs.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCo/Subst.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Type.hs
- compiler/GHC/Core/Type.hs-boot
- compiler/GHC/Core/Unify.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/BooleanFormula.hs
- compiler/GHC/Data/Graph/Color.hs
- compiler/GHC/Data/Maybe.hs
- compiler/GHC/Data/Strict.hs
- compiler/GHC/Data/TrieMap.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config.hs
- compiler/GHC/Driver/Config/CmmToAsm.hs
- compiler/GHC/Driver/Config/StgToCmm.hs
- + compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Errors/Types.hs
- compiler/GHC/Driver/Flags.hs
- + compiler/GHC/Driver/IncludeSpecs.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- + compiler/GHC/Driver/MakeAction.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- + compiler/GHC/Driver/Session/Units.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Extension.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Specificity.hs
- compiler/GHC/Hs/Stats.hs
- compiler/GHC/Hs/Syn/Type.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/Hs/Utils.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Docs.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Foreign/Call.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Match/Constructor.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc/Desugar.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/HsToCore/Types.hs
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Env.hs
- compiler/GHC/Iface/Ext/Ast.hs
- + compiler/GHC/Iface/Flags.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Recomp/Binary.hs
- compiler/GHC/Iface/Recomp/Flags.hs
- compiler/GHC/Iface/Recomp/Types.hs
- compiler/GHC/Iface/Rename.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/IfaceToCore.hs-boot
- compiler/GHC/JS/Opt/Expr.hs
- compiler/GHC/JS/Opt/Simple.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Platform.hs
- compiler/GHC/Platform/LoongArch64.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Fixity.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Debugger.hs
- + compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- + compiler/GHC/Runtime/Eval/Utils.hs
- compiler/GHC/Runtime/Heap/Inspect.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/JS.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Interpreter/Wasm.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/Stg/CSE.hs
- compiler/GHC/Stg/Unarise.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Config.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToCmm/TagCheck.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/SysTools/Process.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Hole/FitTypes.hs
- compiler/GHC/Tc/Errors/Hole/Plugin.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Arrow.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Default.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- − compiler/GHC/Tc/Gen/Rule.hs
- compiler/GHC/Tc/Gen/Sig.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Instance/Family.hs
- compiler/GHC/Tc/Instance/FunDeps.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Irred.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/Solver/Types.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Class.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TcRef.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/Tc/Zonk/Env.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Annotations.hs
- compiler/GHC/Types/Avail.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Breakpoint.hs
- compiler/GHC/Types/CostCentre.hs
- compiler/GHC/Types/CostCentre/State.hs
- compiler/GHC/Types/DefaultEnv.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/ForeignCall.hs
- compiler/GHC/Types/GREInfo.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/HpcInfo.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Literal.hs
- compiler/GHC/Types/Name.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- compiler/GHC/Types/PkgQual.hs
- compiler/GHC/Types/ProfAuto.hs
- compiler/GHC/Types/SafeHaskell.hs
- compiler/GHC/Types/SourceFile.hs
- compiler/GHC/Types/SptEntry.hs
- compiler/GHC/Types/SrcLoc.hs
- compiler/GHC/Types/TyThing/Ppr.hs
- compiler/GHC/Types/Unique/Supply.hs
- compiler/GHC/Types/Var.hs
- compiler/GHC/Types/Var/Env.hs
- compiler/GHC/Unit/External.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/ModDetails.hs
- compiler/GHC/Unit/Module/ModGuts.hs
- compiler/GHC/Unit/Module/ModIface.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Logger.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic.hs
- compiler/GHC/Utils/Unique.hs
- compiler/Language/Haskell/Syntax/Basic.hs
- compiler/Language/Haskell/Syntax/Binds.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Language/Haskell/Syntax/Type.hs
- compiler/Language/Haskell/Syntax/Type.hs-boot
- compiler/ghc.cabal.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/expected-undocumented-flags.txt
- docs/users_guide/exts/ffi.rst
- docs/users_guide/exts/linear_types.rst
- docs/users_guide/exts/monad_comprehensions.rst
- docs/users_guide/exts/named_defaults.rst
- docs/users_guide/exts/overloaded_strings.rst
- docs/users_guide/exts/parallel_list_comprehensions.rst
- docs/users_guide/exts/poly_kinds.rst
- docs/users_guide/exts/pragmas.rst
- + docs/users_guide/exts/type_defaulting.rst
- docs/users_guide/exts/types.rst
- docs/users_guide/ghci.rst
- docs/users_guide/phases.rst
- docs/users_guide/runtime_control.rst
- docs/users_guide/using-concurrent.rst
- docs/users_guide/using-optimisation.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- docs/users_guide/wasm.rst
- + ghc/GHC/Driver/Session/Lint.hs
- + ghc/GHC/Driver/Session/Mode.hs
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/doc/flavours.md
- hadrian/src/CommandLine.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Hadrian/Haskell/Hash.hs
- hadrian/src/Settings.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- libraries/array
- libraries/base/src/GHC/RTS/Flags.hs
- libraries/base/src/GHC/Records.hs
- libraries/base/src/GHC/Stats.hs
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot/GHC/Serialized.hs
- libraries/ghc-experimental/src/GHC/Wasm/Prim.hs
- + libraries/ghc-internal/cbits/int64x2minmax.c
- + libraries/ghc-internal/cbits/vectorQuotRem.c
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Float.hs
- libraries/ghc-internal/src/GHC/Internal/Numeric.hs
- libraries/ghc-internal/src/GHC/Internal/Real.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/ghc-internal/src/GHC/Internal/TypeError.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Exports.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Flag.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Imports.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/ResolvedBCO.hs
- libraries/ghci/GHCi/Server.hs
- libraries/ghci/GHCi/Signals.hs
- libraries/template-haskell/Language/Haskell/TH/Lib.hs
- − libraries/template-haskell/Language/Haskell/TH/Lib/Internal.hs
- libraries/template-haskell/Language/Haskell/TH/Ppr.hs
- libraries/template-haskell/Language/Haskell/TH/PprLib.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/changelog.md
- libraries/template-haskell/template-haskell.cabal.in
- m4/fp_settings.m4
- m4/fptools_set_c_ld_flags.m4
- nofib
- rts/HeapStackCheck.cmm
- rts/IOManager.c
- rts/Interpreter.c
- rts/PrimOps.cmm
- rts/RtsAPI.c
- rts/RtsSymbols.c
- rts/include/HsFFI.h
- rts/include/RtsAPI.h
- rts/linker/MachO.c
- rts/linker/MachOTypes.h
- rts/wasm/JSFFI.c
- rts/wasm/blocker.cmm
- rts/wasm/jsval.cmm
- rts/wasm/scheduler.cmm
- testsuite/driver/junit.py
- testsuite/driver/perf_notes.py
- testsuite/tests/cmm/should_run/AtomicFetch_cmm.cmm
- + testsuite/tests/core-to-stg/T23865.hs
- testsuite/tests/core-to-stg/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/deSugar/should_compile/T10251.stderr
- + testsuite/tests/default/T25775.hs
- + testsuite/tests/default/T25775.stderr
- + testsuite/tests/default/T25857.hs
- + testsuite/tests/default/T25857.stderr
- + testsuite/tests/default/T25858.hs
- + testsuite/tests/default/T25858.stdout
- + testsuite/tests/default/T25858v1.hs
- + testsuite/tests/default/T25858v1.stdout
- + testsuite/tests/default/T25858v1_helper.hs
- + testsuite/tests/default/T25858v2.hs
- + testsuite/tests/default/T25858v2.stdout
- + testsuite/tests/default/T25858v2_helper.hs
- + testsuite/tests/default/T25858v3.hs
- + testsuite/tests/default/T25858v3.stdout
- + testsuite/tests/default/T25858v3_helper.hs
- + testsuite/tests/default/T25858v4.hs
- + testsuite/tests/default/T25858v4.stdout
- + testsuite/tests/default/T25882.hs
- testsuite/tests/default/all.T
- testsuite/tests/default/default-fail01.stderr
- testsuite/tests/default/default-fail02.stderr
- testsuite/tests/default/default-fail04.stderr
- testsuite/tests/default/default-fail08.hs
- testsuite/tests/default/default-fail08.stderr
- + testsuite/tests/dependent/should_compile/GADTSingletons.hs
- + testsuite/tests/dependent/should_compile/T12088a.hs
- + testsuite/tests/dependent/should_compile/T12088b.hs
- + testsuite/tests/dependent/should_compile/T12088c.hs
- + testsuite/tests/dependent/should_compile/T12088d.hs
- + testsuite/tests/dependent/should_compile/T12088e.hs
- + testsuite/tests/dependent/should_compile/T12088sg1.hs
- + testsuite/tests/dependent/should_compile/T12088sg2.hs
- + testsuite/tests/dependent/should_compile/T12088sg3.hs
- + testsuite/tests/dependent/should_compile/T12239.hs
- + testsuite/tests/dependent/should_compile/T14668a.hs
- + testsuite/tests/dependent/should_compile/T14668b.hs
- + testsuite/tests/dependent/should_compile/T15561.hs
- + testsuite/tests/dependent/should_compile/T16410.hs
- + testsuite/tests/dependent/should_compile/T16448.hs
- + testsuite/tests/dependent/should_compile/T16693.hs
- + testsuite/tests/dependent/should_compile/T19611.hs
- + testsuite/tests/dependent/should_compile/T20875.hs
- + testsuite/tests/dependent/should_compile/T21172.hs
- + testsuite/tests/dependent/should_compile/T22257a.hs
- + testsuite/tests/dependent/should_compile/T22257b.hs
- + testsuite/tests/dependent/should_compile/T25238.hs
- + testsuite/tests/dependent/should_compile/T25834.hs
- testsuite/tests/dependent/should_compile/all.T
- testsuite/tests/dependent/should_fail/T16326_Fail8.stderr
- testsuite/tests/deriving/should_compile/T17324.stderr
- testsuite/tests/deriving/should_compile/T17339.stderr
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/driver/RecompCompletePragma/A1.hs
- + testsuite/tests/driver/RecompCompletePragma/A2.hs
- + testsuite/tests/driver/RecompCompletePragma/A3.hs
- + testsuite/tests/driver/RecompCompletePragma/A4.hs
- + testsuite/tests/driver/RecompCompletePragma/B1.hs
- + testsuite/tests/driver/RecompCompletePragma/C1.hs
- + testsuite/tests/driver/RecompCompletePragma/C2.hs
- + testsuite/tests/driver/RecompCompletePragma/C3.hs
- + testsuite/tests/driver/RecompCompletePragma/Makefile
- + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixity.stderr
- + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixity.stdout
- + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixityA.hs
- + testsuite/tests/driver/RecompCompletePragma/RecompCompleteFixityB.hs
- + testsuite/tests/driver/RecompCompletePragma/RecompCompleteIndependence.hs
- + testsuite/tests/driver/RecompCompletePragma/RecompCompleteIndependence.stdout
- + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma.stderr
- + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma.stdout
- + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragma2.stdout
- + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragmaA.hs
- + testsuite/tests/driver/RecompCompletePragma/RecompCompletePragmaB.hs
- + testsuite/tests/driver/RecompCompletePragma/all.T
- + testsuite/tests/driver/RecompExportedDefault/A.hs
- + testsuite/tests/driver/RecompExportedDefault/A2.hs
- + testsuite/tests/driver/RecompExportedDefault/A3.hs
- + testsuite/tests/driver/RecompExportedDefault/A4.hs
- + testsuite/tests/driver/RecompExportedDefault/Makefile
- + testsuite/tests/driver/RecompExportedDefault/RecompExportedDefault.hs
- + testsuite/tests/driver/RecompExportedDefault/RecompExportedDefault.stdout
- + testsuite/tests/driver/RecompExportedDefault/all.T
- + testsuite/tests/driver/RecompExports/Makefile
- + testsuite/tests/driver/RecompExports/RecompExports1.stderr
- + testsuite/tests/driver/RecompExports/RecompExports1.stdout
- + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports1_M.hs_3
- + testsuite/tests/driver/RecompExports/RecompExports1_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports2.stderr
- + testsuite/tests/driver/RecompExports/RecompExports2.stdout
- + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports2_M.hs_3
- + testsuite/tests/driver/RecompExports/RecompExports2_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports3.stderr
- + testsuite/tests/driver/RecompExports/RecompExports3.stdout
- + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports3_M.hs_3
- + testsuite/tests/driver/RecompExports/RecompExports3_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports4.stderr
- + testsuite/tests/driver/RecompExports/RecompExports4.stdout
- + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports4_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports4_N.hs
- + testsuite/tests/driver/RecompExports/RecompExports5.stdout
- + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_1
- + testsuite/tests/driver/RecompExports/RecompExports5_M.hs_2
- + testsuite/tests/driver/RecompExports/RecompExports5_N.hs
- + testsuite/tests/driver/RecompExports/all.T
- testsuite/tests/driver/dynamicToo/dynamicToo001/Makefile
- + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837.stdout
- + testsuite/tests/driver/dynamicToo/dynamicToo001/T25837Module.hs
- testsuite/tests/driver/dynamicToo/dynamicToo001/test.T
- testsuite/tests/driver/inline-check.stderr
- testsuite/tests/ffi/should_compile/all.T
- testsuite/tests/ghc-api/Makefile
- testsuite/tests/ghc-api/T18522-dbg-ppr.hs
- + testsuite/tests/ghc-api/T25577.hs
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-api/exactprint/Test20239.stderr
- testsuite/tests/ghc-api/settings-escape/T11938.hs → testsuite/tests/ghc-api/settings-escape/T24265.hs
- testsuite/tests/ghc-api/settings-escape/T11938.stderr → testsuite/tests/ghc-api/settings-escape/T24265.stderr
- + testsuite/tests/ghc-api/settings-escape/T25204.hs
- + testsuite/tests/ghc-api/settings-escape/T25204.stdout
- + testsuite/tests/ghc-api/settings-escape/T25204_C.c
- testsuite/tests/ghc-api/settings-escape/all.T
- + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/ghc version.h
- testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib/.gitkeep → testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/.gitkeep
- testsuite/tests/ghc-e/should_fail/T9930fail.stderr
- + testsuite/tests/ghci-browser/all.T
- + testsuite/tests/ghci-browser/browser001.script
- + testsuite/tests/ghci-browser/browser001.stdout
- + testsuite/tests/ghci.debugger/scripts/T25932.hs
- + testsuite/tests/ghci.debugger/scripts/T25932.script
- + testsuite/tests/ghci.debugger/scripts/T25932.stdout
- testsuite/tests/ghci.debugger/scripts/T8487.script
- testsuite/tests/ghci.debugger/scripts/all.T
- testsuite/tests/ghci.debugger/scripts/break018.script
- testsuite/tests/ghci.debugger/scripts/break018.stdout
- testsuite/tests/ghci.debugger/scripts/dynbrk004.stdout
- testsuite/tests/ghci.debugger/scripts/dynbrk007.script
- testsuite/tests/ghci.debugger/scripts/dynbrk007.stdout
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T4175.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci064.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T24221.stderr
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- + testsuite/tests/indexed-types/should_compile/T25657.hs
- testsuite/tests/indexed-types/should_compile/all.T
- testsuite/tests/indexed-types/should_fail/T8550.stderr
- testsuite/tests/interface-stability/README.mkd
- testsuite/tests/interface-stability/all.T
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- + testsuite/tests/interface-stability/ghc-bignum-exports.stdout
- + testsuite/tests/interface-stability/ghc-prim-exports.stdout
- + testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/jsffi/all.T
- + testsuite/tests/jsffi/cancel.hs
- + testsuite/tests/jsffi/cancel.mjs
- + testsuite/tests/jsffi/cancel.stdout
- testsuite/tests/jsffi/jsffigc.hs
- + testsuite/tests/linear/should_compile/NonLinearRecord.hs
- testsuite/tests/linear/should_compile/all.T
- + testsuite/tests/linear/should_fail/LinearRecFieldMany.hs
- + testsuite/tests/linear/should_fail/LinearRecFieldMany.stderr
- testsuite/tests/linear/should_fail/all.T
- testsuite/tests/linters/notes.stdout
- + testsuite/tests/llvm/should_run/T25770.hs
- + testsuite/tests/llvm/should_run/T25770.stdout
- testsuite/tests/llvm/should_run/all.T
- testsuite/tests/module/T11970A.stderr
- testsuite/tests/module/all.T
- testsuite/tests/module/mod132.stderr
- testsuite/tests/module/mod147.stderr
- testsuite/tests/module/mod176.stderr
- testsuite/tests/module/mod73.hs
- testsuite/tests/module/mod73.stderr
- testsuite/tests/overloadedrecflds/should_fail/overloadedrecfldsfail06.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/OpaqueParseWarn1.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- testsuite/tests/parser/should_compile/T15279.stderr
- testsuite/tests/parser/should_compile/T20452.stderr
- testsuite/tests/parser/should_fail/T3811c.stderr
- testsuite/tests/parser/should_fail/T7848.stderr
- testsuite/tests/parser/should_fail/readFail038.stderr
- testsuite/tests/parser/should_fail/unpack_inside_type.stderr
- testsuite/tests/partial-sigs/should_fail/WildcardInInstanceHead.stderr
- testsuite/tests/perf/compiler/WWRec.hs
- testsuite/tests/perf/compiler/hard_hole_fits.hs
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/plugins/T20803-plugin/FixErrorsPlugin.hs
- testsuite/tests/plugins/plugins10.stdout
- testsuite/tests/plugins/static-plugins.stdout
- testsuite/tests/polykinds/T18300.hs
- testsuite/tests/polykinds/T18300.stderr
- testsuite/tests/primops/should_run/all.T
- testsuite/tests/printer/Makefile
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/printer/Test24533.stdout
- + testsuite/tests/printer/Test25885.hs
- testsuite/tests/printer/all.T
- testsuite/tests/quasiquotation/T7918.hs
- testsuite/tests/rename/should_compile/T14881.stderr
- + testsuite/tests/rename/should_compile/T24027.hs
- + testsuite/tests/rename/should_compile/T24027_aux.hs
- + testsuite/tests/rename/should_compile/T24035.hs
- + testsuite/tests/rename/should_compile/T24035_aux.hs
- + testsuite/tests/rename/should_compile/T24035b.hs
- + testsuite/tests/rename/should_compile/T24035b.stderr
- + testsuite/tests/rename/should_compile/T25892.hs
- + testsuite/tests/rename/should_compile/T25892_aux.hs
- testsuite/tests/rename/should_compile/all.T
- testsuite/tests/rename/should_fail/SimilarNamesImport.stderr
- testsuite/tests/rename/should_fail/T16114.stderr
- testsuite/tests/rename/should_fail/T18240a.stderr
- testsuite/tests/rename/should_fail/T19843c.stderr
- testsuite/tests/rename/should_fail/T22478b.stderr
- testsuite/tests/rename/should_fail/T22478e.stderr
- testsuite/tests/rename/should_fail/T22478f.stderr
- + testsuite/tests/rename/should_fail/T22688.hs
- + testsuite/tests/rename/should_fail/T22688.stderr
- testsuite/tests/rename/should_fail/T23510a.hs
- testsuite/tests/rename/should_fail/T23510a.stderr
- + testsuite/tests/rename/should_fail/T23982.hs
- + testsuite/tests/rename/should_fail/T23982.stderr
- + testsuite/tests/rename/should_fail/T23982_aux.hs
- + testsuite/tests/rename/should_fail/T23982b.hs
- + testsuite/tests/rename/should_fail/T23982b.stderr
- + testsuite/tests/rename/should_fail/T23982b_aux.hs
- + testsuite/tests/rename/should_fail/T25877.hs
- + testsuite/tests/rename/should_fail/T25877.stderr
- + testsuite/tests/rename/should_fail/T25877_aux.hs
- testsuite/tests/rename/should_fail/T5951.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rep-poly/T14561b.stderr
- testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/rts/T13082/Makefile
- testsuite/tests/rts/T13082/T13082_fail.stderr → testsuite/tests/rts/T13082/T13082_fail.stdout
- testsuite/tests/rts/all.T
- testsuite/tests/saks/should_fail/T16722.stderr
- testsuite/tests/saks/should_fail/saks_fail003.stderr
- testsuite/tests/showIface/Orphans.stdout
- testsuite/tests/simd/should_run/all.T
- + testsuite/tests/simd/should_run/doublex2_arith.hs
- + testsuite/tests/simd/should_run/doublex2_arith.stdout
- + testsuite/tests/simd/should_run/doublex2_arith_baseline.hs
- + testsuite/tests/simd/should_run/doublex2_arith_baseline.stdout
- + testsuite/tests/simd/should_run/doublex2_fma.hs
- + testsuite/tests/simd/should_run/doublex2_fma.stdout
- + testsuite/tests/simd/should_run/floatx4_arith.hs
- + testsuite/tests/simd/should_run/floatx4_arith.stdout
- + testsuite/tests/simd/should_run/floatx4_arith_baseline.hs
- + testsuite/tests/simd/should_run/floatx4_arith_baseline.stdout
- + testsuite/tests/simd/should_run/floatx4_fma.hs
- + testsuite/tests/simd/should_run/floatx4_fma.stdout
- + testsuite/tests/simd/should_run/int16x8_arith.hs
- + testsuite/tests/simd/should_run/int16x8_arith.stdout
- + testsuite/tests/simd/should_run/int16x8_arith_baseline.hs
- + testsuite/tests/simd/should_run/int16x8_arith_baseline.stdout
- + testsuite/tests/simd/should_run/int16x8_shuffle.hs
- + testsuite/tests/simd/should_run/int16x8_shuffle.stdout
- + testsuite/tests/simd/should_run/int16x8_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/int16x8_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/int32x4_arith.hs
- + testsuite/tests/simd/should_run/int32x4_arith.stdout
- + testsuite/tests/simd/should_run/int32x4_arith_baseline.hs
- + testsuite/tests/simd/should_run/int32x4_arith_baseline.stdout
- + testsuite/tests/simd/should_run/int32x4_shuffle.hs
- + testsuite/tests/simd/should_run/int32x4_shuffle.stdout
- + testsuite/tests/simd/should_run/int32x4_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/int32x4_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/int64x2_arith.hs
- + testsuite/tests/simd/should_run/int64x2_arith.stdout
- + testsuite/tests/simd/should_run/int64x2_arith_baseline.hs
- + testsuite/tests/simd/should_run/int64x2_arith_baseline.stdout
- + testsuite/tests/simd/should_run/int64x2_shuffle.hs
- + testsuite/tests/simd/should_run/int64x2_shuffle.stdout
- + testsuite/tests/simd/should_run/int64x2_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/int64x2_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/int8x16_arith.hs
- + testsuite/tests/simd/should_run/int8x16_arith.stdout
- + testsuite/tests/simd/should_run/int8x16_arith_baseline.hs
- + testsuite/tests/simd/should_run/int8x16_arith_baseline.stdout
- + testsuite/tests/simd/should_run/int8x16_shuffle.hs
- + testsuite/tests/simd/should_run/int8x16_shuffle.stdout
- + testsuite/tests/simd/should_run/int8x16_shuffle_baseline.hs
- + testsuite/tests/simd/should_run/int8x16_shuffle_baseline.stdout
- + testsuite/tests/simd/should_run/word16x8_arith.hs
- + testsuite/tests/simd/should_run/word16x8_arith.stdout
- + testsuite/tests/simd/should_run/word16x8_arith_baseline.hs
- + testsuite/tests/simd/should_run/word16x8_arith_baseline.stdout
- + testsuite/tests/simd/should_run/word32x4_arith.hs
- + testsuite/tests/simd/should_run/word32x4_arith.stdout
- + testsuite/tests/simd/should_run/word32x4_arith_baseline.hs
- + testsuite/tests/simd/should_run/word32x4_arith_baseline.stdout
- + testsuite/tests/simd/should_run/word64x2_arith.hs
- + testsuite/tests/simd/should_run/word64x2_arith.stdout
- + testsuite/tests/simd/should_run/word64x2_arith_baseline.hs
- + testsuite/tests/simd/should_run/word64x2_arith_baseline.stdout
- + testsuite/tests/simd/should_run/word8x16_arith.hs
- + testsuite/tests/simd/should_run/word8x16_arith.stdout
- + testsuite/tests/simd/should_run/word8x16_arith_baseline.hs
- + testsuite/tests/simd/should_run/word8x16_arith_baseline.stdout
- + testsuite/tests/simplCore/should_compile/DsSpecPragmas.hs
- + testsuite/tests/simplCore/should_compile/DsSpecPragmas.stderr
- testsuite/tests/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/RewriteHigherOrderPatterns.stderr
- testsuite/tests/simplCore/should_compile/T12603.stdout
- testsuite/tests/simplCore/should_compile/T15445.stderr
- testsuite/tests/simplCore/should_compile/T18013.stderr
- testsuite/tests/simplCore/should_compile/T18668.stderr
- + testsuite/tests/simplCore/should_compile/T24359a.hs
- + testsuite/tests/simplCore/should_compile/T24359a.stderr
- + testsuite/tests/simplCore/should_compile/T25389.hs
- + testsuite/tests/simplCore/should_compile/T25389.stderr
- + testsuite/tests/simplCore/should_compile/T3990b.hs
- + testsuite/tests/simplCore/should_compile/T3990b.stdout
- testsuite/tests/simplCore/should_compile/T4398.stderr
- testsuite/tests/simplCore/should_compile/T5821.hs
- testsuite/tests/simplCore/should_compile/T8537.stderr
- + testsuite/tests/simplCore/should_compile/T9578b.hs
- testsuite/tests/simplCore/should_compile/all.T
- − testsuite/tests/simplCore/should_compile/simpl016.stderr
- + testsuite/tests/simplCore/should_fail/T25117a.hs
- + testsuite/tests/simplCore/should_fail/T25117a.stderr
- + testsuite/tests/simplCore/should_fail/T25117b.hs
- + testsuite/tests/simplCore/should_fail/T25117b.stderr
- + testsuite/tests/simplCore/should_fail/T25672.hs
- + testsuite/tests/simplCore/should_fail/T25672.stderr
- testsuite/tests/simplCore/should_fail/all.T
- + testsuite/tests/simplCore/should_run/T24359b.hs
- + testsuite/tests/simplCore/should_run/T24359b.stdout
- testsuite/tests/simplCore/should_run/all.T
- + testsuite/tests/th/T13123.stderr
- testsuite/tests/th/T15365.stderr
- testsuite/tests/th/T1835.stdout
- testsuite/tests/th/T19363.stdout
- testsuite/tests/th/T7064.stdout
- testsuite/tests/th/TH_pragma.hs
- testsuite/tests/th/TH_pragma.stderr
- testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs
- testsuite/tests/typecheck/should_compile/LoopOfTheDay1.hs
- testsuite/tests/typecheck/should_compile/LoopOfTheDay2.hs
- testsuite/tests/typecheck/should_compile/LoopOfTheDay3.hs
- + testsuite/tests/typecheck/should_compile/RuleEqs.hs
- + testsuite/tests/typecheck/should_compile/RuleEqs.stderr
- testsuite/tests/typecheck/should_compile/T10504.stderr
- + testsuite/tests/typecheck/should_compile/T21003.hs
- testsuite/tests/typecheck/should_compile/T2494.stderr
- + testsuite/tests/typecheck/should_compile/TcSpecPragmas.hs
- + testsuite/tests/typecheck/should_compile/TcSpecPragmas.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/tc186.hs
- testsuite/tests/typecheck/should_compile/tc212.hs
- testsuite/tests/typecheck/should_fail/ExplicitSpecificity5.stderr
- testsuite/tests/typecheck/should_fail/ExplicitSpecificity6.stderr
- + testsuite/tests/typecheck/should_fail/SpecPragmasFail.hs
- + testsuite/tests/typecheck/should_fail/SpecPragmasFail.stderr
- testsuite/tests/typecheck/should_fail/T10495.hs
- testsuite/tests/typecheck/should_fail/T10495.stderr
- testsuite/tests/typecheck/should_fail/T12729.stderr
- testsuite/tests/typecheck/should_fail/T12921.stderr
- testsuite/tests/typecheck/should_fail/T16394.stderr
- testsuite/tests/typecheck/should_fail/T19109.stderr
- testsuite/tests/typecheck/should_fail/T19978.stderr
- testsuite/tests/typecheck/should_fail/T23776.stderr
- + testsuite/tests/typecheck/should_fail/T24090a.hs
- + testsuite/tests/typecheck/should_fail/T24090a.stderr
- + testsuite/tests/typecheck/should_fail/T24090b.hs
- testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr → testsuite/tests/typecheck/should_fail/T24090b.stderr
- + testsuite/tests/typecheck/should_fail/T25004.hs
- + testsuite/tests/typecheck/should_fail/T25004.stderr
- testsuite/tests/typecheck/should_fail/T5853.stderr
- testsuite/tests/typecheck/should_fail/T6018fail.stderr
- testsuite/tests/typecheck/should_fail/T7210.stderr
- testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.hs
- testsuite/tests/typecheck/should_fail/TyAppPat_MisplacedApplication.stderr
- testsuite/tests/typecheck/should_fail/all.T
- + testsuite/tests/typecheck/should_run/T25529.hs
- + testsuite/tests/typecheck/should_run/T25529.stdout
- testsuite/tests/typecheck/should_run/all.T
- + testsuite/tests/warnings/should_compile/SpecMultipleTys.hs
- + testsuite/tests/warnings/should_compile/SpecMultipleTys.stderr
- testsuite/tests/warnings/should_compile/T19296.stderr
- testsuite/tests/warnings/should_compile/WarnNoncanonical.stderr
- testsuite/tests/warnings/should_compile/all.T
- + testsuite/tests/warnings/should_fail/SpecEMultipleTys.hs
- + testsuite/tests/warnings/should_fail/SpecEMultipleTys.stderr
- testsuite/tests/warnings/should_fail/all.T
- testsuite/tests/wasm/should_run/control-flow/README.md
- − testsuite/tests/wasm/should_run/control-flow/WasmControlFlow.stdout
- testsuite/tests/wasm/should_run/control-flow/all.T
- testsuite/tests/wcompat-warnings/Template.hs
- utils/check-exact/ExactPrint.hs
- utils/check-exact/Parsers.hs
- utils/dump-decls/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Interface/RenameType.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/html-test/ref/LinearTypes.html
- utils/haddock/html-test/ref/QuasiExpr.html
- utils/haddock/html-test/ref/TH.html
- utils/haddock/html-test/ref/Threaded_TH.html
- utils/haddock/html-test/src/LinearTypes.hs
- utils/haddock/latex-test/ref/LinearTypes/LinearTypes.tex
- utils/haddock/latex-test/src/LinearTypes/LinearTypes.hs
- utils/jsffi/dyld.mjs
- utils/jsffi/post-link.mjs
- utils/jsffi/prelude.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1263d40ad2072f9eb4eff2ed593811…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1263d40ad2072f9eb4eff2ed593811…
You're receiving this email because of your account on gitlab.haskell.org.
1
0