[Git][ghc/ghc][wip/haanss/depdir] 4 commits: Fix documentation for HEAP_PROF_SAMPLE_STRING
by Hassan Al-Awwadi (@hassan.awwadi) 14 Jul '25
by Hassan Al-Awwadi (@hassan.awwadi) 14 Jul '25
14 Jul '25
Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC
Commits:
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
0bfcaf03 by Hassan Al-Awwadi at 2025-07-14T18:54:33+02:00
Adds the fucnction addDependentDirectory to Q, resolving issue #26148.
This function adds a new directory to the list of things a module depends upon. That means that when the contents of the directory change, the recompilation checker will notice this and the module will be recompiled. Documentation has also been added for addDependentFunction and addDependentDirectory in the user guide.
- - - - -
25 changed files:
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Recomp/Types.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Deps.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/separate_compilation.rst
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/TH.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- testsuite/.gitignore
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/th/Makefile
- + testsuite/tests/th/TH_Depends_Dir.hs
- + testsuite/tests/th/TH_Depends_Dir.stdout
- + testsuite/tests/th/TH_Depends_Dir_External.hs
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Usage.hs
=====================================
@@ -75,14 +75,15 @@ data UsageConfig = UsageConfig
mkUsageInfo :: UsageConfig -> Plugins -> FinderCache -> UnitEnv
-> Module -> ImportedMods -> [ImportUserSpec] -> NameSet
- -> [FilePath] -> [(Module, Fingerprint)] -> [Linkable] -> PkgsLoaded
+ -> [FilePath] -> [FilePath] -> [(Module, Fingerprint)] -> [Linkable] -> PkgsLoaded
-> IfG [Usage]
mkUsageInfo uc plugins fc unit_env
this_mod dir_imp_mods imp_decls used_names
- dependent_files merged needed_links needed_pkgs
+ dependent_files dependent_dirs merged needed_links needed_pkgs
= do
eps <- liftIO $ readIORef (euc_eps (ue_eps unit_env))
- hashes <- liftIO $ mapM getFileHash dependent_files
+ file_hashes <- liftIO $ mapM getFileHash dependent_files
+ dirs_hashes <- liftIO $ mapM getDirHash dependent_dirs
let hu = ue_unsafeHomeUnit unit_env
hug = ue_home_unit_graph unit_env
-- Dependencies on object files due to TH and plugins
@@ -93,7 +94,11 @@ mkUsageInfo uc plugins fc unit_env
let usages = mod_usages ++ [ UsageFile { usg_file_path = mkFastString f
, usg_file_hash = hash
, usg_file_label = Nothing }
- | (f, hash) <- zip dependent_files hashes ]
+ | (f, hash) <- zip dependent_files file_hashes ]
+ ++ [ UsageDirectory { usg_dir_path = mkFastString d
+ , usg_dir_hash = hash
+ , usg_dir_label = Nothing }
+ | (d, hash) <- zip dependent_dirs dirs_hashes]
++ [ UsageMergedRequirement
{ usg_mod = mod,
usg_mod_hash = hash
=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -269,6 +269,7 @@ mkRecompUsageInfo hsc_env tc_result = do
else do
let used_names = mkUsedNames tc_result
dep_files <- (readIORef (tcg_dependent_files tc_result))
+ dep_dirs <- (readIORef (tcg_dependent_dirs tc_result))
(needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result)
let uc = initUsageConfig hsc_env
plugins = hsc_plugins hsc_env
@@ -289,6 +290,7 @@ mkRecompUsageInfo hsc_env tc_result = do
(tcg_import_decls tc_result)
used_names
dep_files
+ dep_dirs
(tcg_merged tc_result)
needed_links
needed_pkgs
=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -194,6 +194,7 @@ data RecompReason
| ModuleChangedRaw ModuleName
| ModuleChangedIface ModuleName
| FileChanged FilePath
+ | DirChanged FilePath
| CustomReason String
| FlagsChanged
| LinkFlagsChanged
@@ -230,6 +231,7 @@ instance Outputable RecompReason where
ModuleRemoved (_st, _uid, m) -> ppr m <+> text "removed"
ModuleAdded (_st, _uid, m) -> ppr m <+> text "added"
FileChanged fp -> text fp <+> text "changed"
+ DirChanged dp -> text dp <+> text "changed"
CustomReason s -> text s
FlagsChanged -> text "Flags changed"
LinkFlagsChanged -> text "Flags changed"
@@ -815,6 +817,22 @@ checkModUsage fc UsageFile{ usg_file_path = file,
then \e -> pprTrace "UsageFile" (text (show e)) $ return recomp
else \_ -> return recomp -- if we can't find the file, just recompile, don't fail
+checkModUsage fc UsageDirectory{ usg_dir_path = dir,
+ usg_dir_hash = old_hash,
+ usg_dir_label = mlabel } =
+ liftIO $
+ handleIO handler $ do
+ new_hash <- lookupDirCache fc $ unpackFS dir
+ if (old_hash /= new_hash)
+ then return recomp
+ else return UpToDate
+ where
+ reason = DirChanged $ unpackFS dir
+ recomp = needsRecompileBecause $ fromMaybe reason $ fmap CustomReason mlabel
+ handler = if debugIsOn
+ then \e -> pprTrace "UsageDirectory" (text (show e)) $ return recomp
+ else \_ -> return recomp -- if we can't find the dir, just recompile, don't fail
+
-- | We are importing a module whose exports have changed.
-- Does this require recompilation?
--
=====================================
compiler/GHC/Iface/Recomp/Types.hs
=====================================
@@ -140,6 +140,10 @@ pprUsage usage@UsageFile{}
= hsep [text "addDependentFile",
doubleQuotes (ftext (usg_file_path usage)),
ppr (usg_file_hash usage)]
+pprUsage usage@UsageDirectory{}
+ = hsep [text "AddDependentDirectory",
+ doubleQuotes (ftext (usg_dir_path usage)),
+ ppr (usg_dir_hash usage)]
pprUsage usage@UsageMergedRequirement{}
= hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)]
pprUsage usage@UsageHomeModuleInterface{}
=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -173,8 +173,6 @@ import GHC.Parser.HaddockLex (lexHsDoc)
import GHC.Parser (parseIdentifier)
import GHC.Rename.Doc (rnHsDoc)
-
-
{-
Note [Template Haskell state diagram]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1524,6 +1522,11 @@ instance TH.Quasi TcM where
dep_files <- readTcRef ref
writeTcRef ref (fp:dep_files)
+ qAddDependentDirectory dp = do
+ ref <- fmap tcg_dependent_dirs getGblEnv
+ dep_dirs <- readTcRef ref
+ writeTcRef ref (dp:dep_dirs)
+
qAddTempFile suffix = do
dflags <- getDynFlags
logger <- getLogger
@@ -1928,6 +1931,7 @@ handleTHMessage msg = case msg of
ReifyConStrictness nm -> wrapTHResult $ TH.qReifyConStrictness nm
GetPackageRoot -> wrapTHResult $ TH.qGetPackageRoot
AddDependentFile f -> wrapTHResult $ TH.qAddDependentFile f
+ AddDependentDirectory d -> wrapTHResult $ TH.qAddDependentDirectory d
AddTempFile s -> wrapTHResult $ TH.qAddTempFile s
AddModFinalizer r -> do
interp <- hscInterp <$> getTopEnv
=====================================
compiler/GHC/Tc/Types.hs
=====================================
@@ -603,6 +603,7 @@ data TcGblEnv
-- decls.
tcg_dependent_files :: TcRef [FilePath], -- ^ dependencies from addDependentFile
+ tcg_dependent_dirs :: TcRef [FilePath], -- ^ dependencies from addDependentDirectory
tcg_th_topdecls :: TcRef [LHsDecl GhcPs],
-- ^ Top-level declarations from addTopDecls
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -55,7 +55,7 @@ module GHC.Tc.Utils.Monad(
getRdrEnvs, getImports,
getFixityEnv, extendFixityEnv,
getDeclaredDefaultTys,
- addDependentFiles,
+ addDependentFiles, addDependentDirectories,
-- * Error management
getSrcSpanM, setSrcSpan, setSrcSpanA, addLocM,
@@ -274,6 +274,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
let { type_env_var = hsc_type_env_vars hsc_env };
dependent_files_var <- newIORef [] ;
+ dependent_dirs_var <- newIORef [] ;
static_wc_var <- newIORef emptyWC ;
cc_st_var <- newIORef newCostCentreState ;
th_topdecls_var <- newIORef [] ;
@@ -369,6 +370,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
tcg_safe_infer = infer_var,
tcg_safe_infer_reasons = infer_reasons_var,
tcg_dependent_files = dependent_files_var,
+ tcg_dependent_dirs = dependent_dirs_var,
tcg_tc_plugin_solvers = [],
tcg_tc_plugin_rewriters = emptyUFM,
tcg_defaulting_plugins = [],
@@ -957,6 +959,12 @@ addDependentFiles fs = do
dep_files <- readTcRef ref
writeTcRef ref (fs ++ dep_files)
+addDependentDirectories :: [FilePath] -> TcRn ()
+addDependentDirectories ds = do
+ ref <- fmap tcg_dependent_dirs getGblEnv
+ dep_dirs <- readTcRef ref
+ writeTcRef ref (ds ++ dep_dirs)
+
{-
************************************************************************
* *
=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -31,6 +31,9 @@ module GHC.Unit.Finder (
findObjectLinkableMaybe,
findObjectLinkable,
+
+ -- important that GHC.HsToCore.Usage uses the same hashing method for usage dirs as is used here.
+ getDirHash,
) where
import GHC.Prelude
@@ -68,7 +71,9 @@ import qualified Data.Map as M
import GHC.Driver.Env
import GHC.Driver.Config.Finder
import qualified Data.Set as Set
+import qualified Data.List as L(sort)
import Data.List.NonEmpty ( NonEmpty (..) )
+import qualified System.Directory as SD
import qualified System.OsPath as OsPath
import qualified Data.List.NonEmpty as NE
@@ -107,10 +112,12 @@ initFinderCache :: IO FinderCache
initFinderCache = do
mod_cache <- newIORef emptyInstalledModuleEnv
file_cache <- newIORef M.empty
+ dir_cache <- newIORef M.empty
let flushFinderCaches :: UnitEnv -> IO ()
flushFinderCaches ue = do
atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
atomicModifyIORef' file_cache $ \_ -> (M.empty, ())
+ atomicModifyIORef' dir_cache $ \_ -> (M.empty, ())
where
is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
@@ -137,8 +144,29 @@ initFinderCache = do
atomicModifyIORef' file_cache $ \c -> (M.insert key hash c, ())
return hash
Just fp -> return fp
+ lookupDirCache :: FilePath -> IO Fingerprint
+ lookupDirCache key = do
+ c <- readIORef dir_cache
+ case M.lookup key c of
+ Nothing -> do
+ hash <- getDirHash key
+ atomicModifyIORef' dir_cache $ \c -> (M.insert key hash c, ())
+ return hash
+ Just fp -> return fp
return FinderCache{..}
+-- | This function computes a shallow hash of a directory, so really just what files and directories are directly inside it.
+-- It does not look at the contents of the files, or the contents of the directories it contains.
+getDirHash :: FilePath -> IO Fingerprint
+getDirHash dir = do
+ contents <- SD.listDirectory dir
+ -- The documentation of Fingerprints describes this as an easy naive implementation
+ -- I wonder if we should do something more sophisticated here?
+ let hashes = fingerprintString <$> contents
+ let s_hashes = L.sort hashes
+ let hash = fingerprintFingerprints s_hashes
+ return hash
+
-- -----------------------------------------------------------------------------
-- The three external entry points
=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -37,6 +37,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
, lookupFileCache :: FilePath -> IO Fingerprint
-- ^ Look for the hash of a file in the cache. This should add it to the
-- cache. If the file doesn't exist, raise an IOException.
+ , lookupDirCache :: FilePath -> IO Fingerprint
}
data InstalledFindResult
=====================================
compiler/GHC/Unit/Module/Deps.hs
=====================================
@@ -357,6 +357,23 @@ data Usage
-- contents don't change. This previously lead to odd
-- recompilation behaviors; see #8114
}
+ | UsageDirectory {
+ usg_dir_path :: FastString,
+ -- ^ External dir dependency. From TH addDependentFile.
+ -- Should be absolute.
+ usg_dir_hash :: Fingerprint,
+ -- ^ 'Fingerprint' of the directories contents.
+
+ usg_dir_label :: Maybe String
+ -- ^ An optional string which is used in recompilation messages if
+ -- dir in question has changed.
+
+ -- Note: We do a very shallow check indeed, just what the contents of
+ -- the directory are, aka what files and directories are within it.
+ -- If those files/directories have their own contents changed...
+ -- We won't spot it here, better recursive add them to your usage
+ -- seperately.
+ }
| UsageHomeModuleInterface {
usg_mod_name :: ModuleName
-- ^ Name of the module
@@ -395,6 +412,7 @@ instance NFData Usage where
rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` ()
rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` ()
rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` ()
+ rnf (UsageDirectory dir hash label) = rnf dir `seq` rnf hash `seq` rnf label `seq` ()
rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` ()
rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` ()
@@ -431,6 +449,12 @@ instance Binary Usage where
put_ bh (usg_unit_id usg)
put_ bh (usg_iface_hash usg)
+ put_ bh usg@UsageDirectory{} = do
+ putByte bh 5
+ put_ bh (usg_dir_path usg)
+ put_ bh (usg_dir_hash usg)
+ put_ bh (usg_dir_label usg)
+
get bh = do
h <- getByte bh
case h of
@@ -462,6 +486,12 @@ instance Binary Usage where
uid <- get bh
hash <- get bh
return UsageHomeModuleInterface { usg_mod_name = mod, usg_unit_id = uid, usg_iface_hash = hash }
+ 5 -> do
+ dp <- get bh
+ hash <- get bh
+ label <- get bh
+ return UsageDirectory { usg_dir_path = dp, usg_dir_hash = hash, usg_dir_label = label }
+
i -> error ("Binary.get(Usage): " ++ show i)
-- | Records the imports that we depend on from a home module,
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -232,6 +232,11 @@ Cmm
They are replaced, respectively, by ``SpecialiseEP``, ``pragSpecED`` and
``pragSpecInlED``.
+- We have added the ``addDependentDirectory`` function to match
+ ``addDependentFile``, which adds a directory to the list of dependencies that
+ the recompilation checker will look at to determine if a module needs to be
+ recompiled.
+
Included libraries
~~~~~~~~~~~~~~~~~~
=====================================
docs/users_guide/eventlog-formats.rst
=====================================
@@ -779,9 +779,9 @@ the total time spent profiling.
Cost-centre break-down
^^^^^^^^^^^^^^^^^^^^^^
-A variable-length packet encoding a heap profile sample broken down by,
- * cost-centre (:rts-flag:`-hc`)
-
+A variable-length packet encoding a heap profile sample.
+This event is only emitted when the heap profile type is set to :rts-flag:`-hc` or :rts-flag:`-hb`.
+Otherwise, a :event-type:`HEAP_PROF_SAMPLE_STRING` event is emitted instead.
.. event-type:: HEAP_PROF_SAMPLE_COST_CENTRE
@@ -796,11 +796,19 @@ A variable-length packet encoding a heap profile sample broken down by,
String break-down
^^^^^^^^^^^^^^^^^
-A variable-length event encoding a heap sample broken down by,
+A variable-length event encoding a heap sample.
+The content of the sample label varies depending on the heap profile type:
+
+ * :rts-flag:`-hT` The sample label contains a closure type, e.g., ``"ghc-bignum:GHC.Num.Integer.IS"``.
+ * :rts-flag:`-hm` The sample label contains a module name, e.g., ``"GHC.Num.Integer"``.
+ * :rts-flag:`-hd` The sample label contains a closure description, e.g., ``"IS"``.
+ * :rts-flag:`-hy` The sample label contains a type description, e.g., ``"Integer"``.
+ * :rts-flag:`-he` The sample label contains a stringified era, e.g., ``"1"``.
+ * :rts-flag:`-hr` The sample label contains a retainer set description, e.g., ``"(184)$stoIntegralSized1"``.
+ * :rts-flag:`-hi` The sample label contains a stringified pointer, e.g., ``"0x1008b7588"``,
+ which can be matched to an info table description emitted by the :event-type:`IPE` event.
- * type description (:rts-flag:`-hy`)
- * closure description (:rts-flag:`-hd`)
- * module (:rts-flag:`-hm`)
+If the heap profile type is set to :rts-flag:`-hc` or :rts-flag:`-hb`, a :event-type:`HEAP_PROF_SAMPLE_COST_CENTRE` event is emitted instead.
.. event-type:: HEAP_PROF_SAMPLE_STRING
@@ -808,7 +816,7 @@ A variable-length event encoding a heap sample broken down by,
:length: variable
:field Word8: profile ID
:field Word64: heap residency in bytes
- :field String: type or closure description, or module name
+ :field String: sample label
.. _time-profiler-events:
=====================================
docs/users_guide/separate_compilation.rst
=====================================
@@ -710,7 +710,7 @@ beautiful sight!
You can read about :ghc-wiki:`how all this works <commentary/compiler/recompilation-avoidance>` in the GHC commentary.
Recompilation for Template Haskell and Plugins
-^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Recompilation checking gets a bit more complicated when using Template Haskell or
plugins. Both these features execute code at compile time and so if any of the
@@ -727,6 +727,19 @@ if ``foo`` is from module ``A`` and ``bar`` is from module ``B``, the module wil
now depend on ``A.o`` and ``B.o``, if either of these change then the module will
be recompiled.
+``addDependentFile`` and ``addDependentDirectory``
+^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
+
+When using Template Haskell or plugins, you can use the functions
+``addDependentFile`` and ``addDependentDirectory`` to add additional
+dependencies to the module being compiled.
+
+- When adding a file, this means that the contents of the file changing between
+ compilations will trigger a recompilation of the module.
+- When adding a directory, this means that any file or subdirectory *added* to or
+ *removed* from the directory will trigger recompilation of the module, so
+ it is not a recursive dependency.
+
.. _mutual-recursion:
Mutually recursive modules and hs-boot files
=====================================
libraries/ghc-internal/src/GHC/Internal/Base.hs
=====================================
@@ -1047,7 +1047,7 @@ class Functor f where
-- * sequence computations and combine their results ('<*>' and 'liftA2').
--
-- A minimal complete definition must include implementations of 'pure'
--- and of either '<*>' or 'liftA2'. If it defines both, then they must behave
+-- and one of either '<*>' or 'liftA2'. If it defines both, then they must behave
-- the same as their default definitions:
--
-- @('<*>') = 'liftA2' 'id'@
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -135,6 +135,9 @@ class (MonadIO m, MonadFail m) => Quasi m where
-- | See 'addDependentFile'.
qAddDependentFile :: FilePath -> m ()
+ -- | See 'addDependentDirectory'.
+ qAddDependentDirectory :: FilePath -> m ()
+
-- | See 'addTempFile'.
qAddTempFile :: String -> m FilePath
@@ -181,30 +184,31 @@ instance Quasi IO where
qReport True msg = hPutStrLn stderr ("Template Haskell error: " ++ msg)
qReport False msg = hPutStrLn stderr ("Template Haskell error: " ++ msg)
- qLookupName _ _ = badIO "lookupName"
- qReify _ = badIO "reify"
- qReifyFixity _ = badIO "reifyFixity"
- qReifyType _ = badIO "reifyFixity"
- qReifyInstances _ _ = badIO "reifyInstances"
- qReifyRoles _ = badIO "reifyRoles"
- qReifyAnnotations _ = badIO "reifyAnnotations"
- qReifyModule _ = badIO "reifyModule"
- qReifyConStrictness _ = badIO "reifyConStrictness"
- qLocation = badIO "currentLocation"
- qRecover _ _ = badIO "recover" -- Maybe we could fix this?
- qGetPackageRoot = badIO "getProjectRoot"
- qAddDependentFile _ = badIO "addDependentFile"
- qAddTempFile _ = badIO "addTempFile"
- qAddTopDecls _ = badIO "addTopDecls"
- qAddForeignFilePath _ _ = badIO "addForeignFilePath"
- qAddModFinalizer _ = badIO "addModFinalizer"
- qAddCorePlugin _ = badIO "addCorePlugin"
- qGetQ = badIO "getQ"
- qPutQ _ = badIO "putQ"
- qIsExtEnabled _ = badIO "isExtEnabled"
- qExtsEnabled = badIO "extsEnabled"
- qPutDoc _ _ = badIO "putDoc"
- qGetDoc _ = badIO "getDoc"
+ qLookupName _ _ = badIO "lookupName"
+ qReify _ = badIO "reify"
+ qReifyFixity _ = badIO "reifyFixity"
+ qReifyType _ = badIO "reifyFixity"
+ qReifyInstances _ _ = badIO "reifyInstances"
+ qReifyRoles _ = badIO "reifyRoles"
+ qReifyAnnotations _ = badIO "reifyAnnotations"
+ qReifyModule _ = badIO "reifyModule"
+ qReifyConStrictness _ = badIO "reifyConStrictness"
+ qLocation = badIO "currentLocation"
+ qRecover _ _ = badIO "recover" -- Maybe we could fix this?
+ qGetPackageRoot = badIO "getProjectRoot"
+ qAddDependentFile _ = badIO "addDependentFile"
+ qAddDependentDirectory _ = badIO "AddDependentDirectory"
+ qAddTempFile _ = badIO "addTempFile"
+ qAddTopDecls _ = badIO "addTopDecls"
+ qAddForeignFilePath _ _ = badIO "addForeignFilePath"
+ qAddModFinalizer _ = badIO "addModFinalizer"
+ qAddCorePlugin _ = badIO "addCorePlugin"
+ qGetQ = badIO "getQ"
+ qPutQ _ = badIO "putQ"
+ qIsExtEnabled _ = badIO "isExtEnabled"
+ qExtsEnabled = badIO "extsEnabled"
+ qPutDoc _ _ = badIO "putDoc"
+ qGetDoc _ = badIO "getDoc"
instance Quote IO where
newName = newNameIO
@@ -822,6 +826,26 @@ getPackageRoot :: Q FilePath
getPackageRoot = Q qGetPackageRoot
+-- | Record external directories that runIO is using (dependent upon).
+-- The compiler can then recognize that it should re-compile the Haskell file
+-- when a directory changes.
+--
+-- Expects an absolute directory path.
+--
+-- Notes:
+--
+-- * ghc -M does not know about these dependencies - it does not execute TH.
+--
+-- * The dependency is shallow, based only on the direct content.
+-- Basically, it only sees a list of names. It does not look at directory
+-- metadata, recurse into subdirectories, or look at file contents. As
+-- long as the list of names remains the same, the directory is considered
+-- unchanged.
+--
+-- * The state of the directory is read at the interface generation time,
+-- not at the time of the function call.
+addDependentDirectory :: FilePath -> Q ()
+addDependentDirectory dp = Q (qAddDependentDirectory dp)
-- | Record external files that runIO is using (dependent upon).
-- The compiler can then recognize that it should re-compile the Haskell file
@@ -833,7 +857,11 @@ getPackageRoot = Q qGetPackageRoot
--
-- * ghc -M does not know about these dependencies - it does not execute TH.
--
--- * The dependency is based on file content, not a modification time
+-- * The dependency is based on file content, not a modification time or
+-- any other metadata associated with the file (e.g. permissions).
+--
+-- * The state of the file is read at the interface generation time,
+-- not at the time of the function call.
addDependentFile :: FilePath -> Q ()
addDependentFile fp = Q (qAddDependentFile fp)
@@ -961,32 +989,33 @@ instance MonadIO Q where
liftIO = runIO
instance Quasi Q where
- qNewName = newName
- qReport = report
- qRecover = recover
- qReify = reify
- qReifyFixity = reifyFixity
- qReifyType = reifyType
- qReifyInstances = reifyInstances
- qReifyRoles = reifyRoles
- qReifyAnnotations = reifyAnnotations
- qReifyModule = reifyModule
- qReifyConStrictness = reifyConStrictness
- qLookupName = lookupName
- qLocation = location
- qGetPackageRoot = getPackageRoot
- qAddDependentFile = addDependentFile
- qAddTempFile = addTempFile
- qAddTopDecls = addTopDecls
- qAddForeignFilePath = addForeignFilePath
- qAddModFinalizer = addModFinalizer
- qAddCorePlugin = addCorePlugin
- qGetQ = getQ
- qPutQ = putQ
- qIsExtEnabled = isExtEnabled
- qExtsEnabled = extsEnabled
- qPutDoc = putDoc
- qGetDoc = getDoc
+ qNewName = newName
+ qReport = report
+ qRecover = recover
+ qReify = reify
+ qReifyFixity = reifyFixity
+ qReifyType = reifyType
+ qReifyInstances = reifyInstances
+ qReifyRoles = reifyRoles
+ qReifyAnnotations = reifyAnnotations
+ qReifyModule = reifyModule
+ qReifyConStrictness = reifyConStrictness
+ qLookupName = lookupName
+ qLocation = location
+ qGetPackageRoot = getPackageRoot
+ qAddDependentFile = addDependentFile
+ qAddDependentDirectory = addDependentDirectory
+ qAddTempFile = addTempFile
+ qAddTopDecls = addTopDecls
+ qAddForeignFilePath = addForeignFilePath
+ qAddModFinalizer = addModFinalizer
+ qAddCorePlugin = addCorePlugin
+ qGetQ = getQ
+ qPutQ = putQ
+ qIsExtEnabled = isExtEnabled
+ qExtsEnabled = extsEnabled
+ qPutDoc = putDoc
+ qGetDoc = getDoc
----------------------------------------------------
=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -291,6 +291,7 @@ data THMessage a where
GetPackageRoot :: THMessage (THResult FilePath)
AddDependentFile :: FilePath -> THMessage (THResult ())
+ AddDependentDirectory :: FilePath -> THMessage (THResult ())
AddTempFile :: String -> THMessage (THResult FilePath)
AddModFinalizer :: RemoteRef (TH.Q ()) -> THMessage (THResult ())
AddCorePlugin :: String -> THMessage (THResult ())
@@ -343,6 +344,7 @@ getTHMessage = do
23 -> THMsg <$> (PutDoc <$> get <*> get)
24 -> THMsg <$> GetDoc <$> get
25 -> THMsg <$> return GetPackageRoot
+ 26 -> THMsg <$> AddDependentDirectory <$> get
n -> error ("getTHMessage: unknown message " ++ show n)
putTHMessage :: THMessage a -> Put
@@ -373,7 +375,7 @@ putTHMessage m = case m of
PutDoc l s -> putWord8 23 >> put l >> put s
GetDoc l -> putWord8 24 >> put l
GetPackageRoot -> putWord8 25
-
+ AddDependentDirectory a -> putWord8 26 >> put a
data EvalOpts = EvalOpts
{ useSandboxThread :: Bool
=====================================
libraries/ghci/GHCi/TH.hs
=====================================
@@ -198,6 +198,7 @@ instance TH.Quasi GHCiQ where
qLocation = fromMaybe noLoc . qsLocation <$> getState
qGetPackageRoot = ghcCmd GetPackageRoot
qAddDependentFile file = ghcCmd (AddDependentFile file)
+ qAddDependentDirectory dir = ghcCmd (AddDependentDirectory dir)
qAddTempFile suffix = ghcCmd (AddTempFile suffix)
qAddTopDecls decls = ghcCmd (AddTopDecls decls)
qAddForeignFilePath lang fp = ghcCmd (AddForeignFilePath lang fp)
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -32,6 +32,7 @@ module Language.Haskell.TH.Syntax (
ModName (..),
addCorePlugin,
addDependentFile,
+ addDependentDirectory,
addForeignFile,
addForeignFilePath,
addForeignSource,
=====================================
testsuite/.gitignore
=====================================
@@ -1523,6 +1523,7 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk
/tests/th/T8633
/tests/th/TH_Depends
/tests/th/TH_Depends_external.txt
+/tests/th/TH_Depends_external/dummy.txt
/tests/th/TH_StringPrimL
/tests/th/TH_import_loop/ModuleA.hi-boot
/tests/th/TH_import_loop/ModuleA.o-boot
=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1715,6 +1715,7 @@ module Language.Haskell.TH.Syntax where
qRunIO :: forall a. GHC.Internal.Types.IO a -> m a
qGetPackageRoot :: m GHC.Internal.IO.FilePath
qAddDependentFile :: GHC.Internal.IO.FilePath -> m ()
+ qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m ()
qAddTempFile :: GHC.Internal.Base.String -> m GHC.Internal.IO.FilePath
qAddTopDecls :: [Dec] -> m ()
qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m ()
@@ -1726,7 +1727,7 @@ module Language.Haskell.TH.Syntax where
qExtsEnabled :: m [Extension]
qPutDoc :: DocLoc -> GHC.Internal.Base.String -> m ()
qGetDoc :: DocLoc -> m (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
- {-# MINIMAL qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc #-}
+ {-# MINIMAL qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddDependentDirectory, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc #-}
type Quote :: (* -> *) -> Constraint
class GHC.Internal.Base.Monad m => Quote m where
newName :: GHC.Internal.Base.String -> m Name
@@ -1779,6 +1780,7 @@ module Language.Haskell.TH.Syntax where
type VarStrictType :: *
type VarStrictType = VarBangType
addCorePlugin :: GHC.Internal.Base.String -> Q ()
+ addDependentDirectory :: GHC.Internal.IO.FilePath -> Q ()
addDependentFile :: GHC.Internal.IO.FilePath -> Q ()
addForeignFile :: ForeignSrcLang -> GHC.Internal.Base.String -> Q ()
addForeignFilePath :: ForeignSrcLang -> GHC.Internal.IO.FilePath -> Q ()
=====================================
testsuite/tests/th/Makefile
=====================================
@@ -43,6 +43,20 @@ TH_Depends:
'$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends
./TH_Depends
+.PHONY: TH_Depends_Dir
+TH_Depends_Dir:
+ rm -rf TH_Depends_external
+ $(RM) TH_Depends_Dir TH_Depends_Dir.exe
+ $(RM) TH_Depends_Dir.o TH_Depends_Dir.hi
+ $(RM) TH_Depends_Dir_External.o TH_Depends_Dir_External.hi
+
+ mkdir TH_Depends_external
+ '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir
+ ./TH_Depends_Dir
+ sleep 2
+ echo "dummy" > TH_Depends_external/dummy.txt
+ '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir
+ ./TH_Depends_Dir
T8333:
'$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) $(ghcThWayFlags) T8333.hs < /dev/null
=====================================
testsuite/tests/th/TH_Depends_Dir.hs
=====================================
@@ -0,0 +1,9 @@
+
+{-# LANGUAGE TemplateHaskell #-}
+
+module Main where
+
+import TH_Depends_Dir_External (checkDirectoryContent)
+
+main :: IO ()
+main = putStrLn $checkDirectoryContent
\ No newline at end of file
=====================================
testsuite/tests/th/TH_Depends_Dir.stdout
=====================================
@@ -0,0 +1,2 @@
+no files?
+yes files!
\ No newline at end of file
=====================================
testsuite/tests/th/TH_Depends_Dir_External.hs
=====================================
@@ -0,0 +1,15 @@
+
+module TH_Depends_Dir_External where
+
+import Language.Haskell.TH.Syntax
+import Language.Haskell.TH.Lib
+import System.Directory (listDirectory)
+
+checkDirectoryContent :: Q Exp
+checkDirectoryContent = do
+ qAddDependentDirectory "TH_Depends_external"
+ l <- qRunIO $ listDirectory "TH_Depends_external"
+ let s = case l of
+ [] -> "no files?"
+ _ -> "yes files!"
+ stringE s
\ No newline at end of file
=====================================
testsuite/tests/th/all.T
=====================================
@@ -214,6 +214,7 @@ test('T5434', [], multimod_compile,
['T5434', '-v0 -Wall ' + config.ghc_th_way_flags])
test('T5508', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('TH_Depends', [only_ways(['normal'])], makefile_test, ['TH_Depends'])
+test('TH_Depends_Dir', [only_ways(['normal'])], makefile_test, ['TH_Depends_Dir'])
test('T5597', [], multimod_compile, ['T5597', '-v0 ' + config.ghc_th_way_flags])
test('T5665', [], multimod_compile, ['T5665', '-v0 ' + config.ghc_th_way_flags])
test('T5700', [], multimod_compile,
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/43229cd960b8bcb6476073d57a8c70…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/43229cd960b8bcb6476073d57a8c70…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/haanss/depdir] Adds the fucnction addDependentDirectory to Q, resolving issue #26148.
by Hassan Al-Awwadi (@hassan.awwadi) 14 Jul '25
by Hassan Al-Awwadi (@hassan.awwadi) 14 Jul '25
14 Jul '25
Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC
Commits:
43229cd9 by Hassan Al-Awwadi at 2025-07-14T18:53:06+02:00
Adds the fucnction addDependentDirectory to Q, resolving issue #26148.
This function adds a new directory to the list of things a module depends upon. That means that when the contents of the directory change, the recompilation checker will notice this and the module will be recompiled. Documentation has also been added for addDependentFunction and addDependentDirectory in the user guide.
- - - - -
23 changed files:
- compiler/GHC/HsToCore/Usage.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Recomp/Types.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Unit/Finder.hs
- compiler/GHC/Unit/Finder/Types.hs
- compiler/GHC/Unit/Module/Deps.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/separate_compilation.rst
- libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/TH.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- testsuite/.gitignore
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/th/Makefile
- + testsuite/tests/th/TH_Depends_Dir.hs
- + testsuite/tests/th/TH_Depends_Dir.stdout
- + testsuite/tests/th/TH_Depends_Dir_External.hs
- testsuite/tests/th/all.T
Changes:
=====================================
compiler/GHC/HsToCore/Usage.hs
=====================================
@@ -75,14 +75,15 @@ data UsageConfig = UsageConfig
mkUsageInfo :: UsageConfig -> Plugins -> FinderCache -> UnitEnv
-> Module -> ImportedMods -> [ImportUserSpec] -> NameSet
- -> [FilePath] -> [(Module, Fingerprint)] -> [Linkable] -> PkgsLoaded
+ -> [FilePath] -> [FilePath] -> [(Module, Fingerprint)] -> [Linkable] -> PkgsLoaded
-> IfG [Usage]
mkUsageInfo uc plugins fc unit_env
this_mod dir_imp_mods imp_decls used_names
- dependent_files merged needed_links needed_pkgs
+ dependent_files dependent_dirs merged needed_links needed_pkgs
= do
eps <- liftIO $ readIORef (euc_eps (ue_eps unit_env))
- hashes <- liftIO $ mapM getFileHash dependent_files
+ file_hashes <- liftIO $ mapM getFileHash dependent_files
+ dirs_hashes <- liftIO $ mapM getDirHash dependent_dirs
let hu = ue_unsafeHomeUnit unit_env
hug = ue_home_unit_graph unit_env
-- Dependencies on object files due to TH and plugins
@@ -93,7 +94,11 @@ mkUsageInfo uc plugins fc unit_env
let usages = mod_usages ++ [ UsageFile { usg_file_path = mkFastString f
, usg_file_hash = hash
, usg_file_label = Nothing }
- | (f, hash) <- zip dependent_files hashes ]
+ | (f, hash) <- zip dependent_files file_hashes ]
+ ++ [ UsageDirectory { usg_dir_path = mkFastString d
+ , usg_dir_hash = hash
+ , usg_dir_label = Nothing }
+ | (d, hash) <- zip dependent_dirs dirs_hashes]
++ [ UsageMergedRequirement
{ usg_mod = mod,
usg_mod_hash = hash
=====================================
compiler/GHC/Iface/Make.hs
=====================================
@@ -269,6 +269,7 @@ mkRecompUsageInfo hsc_env tc_result = do
else do
let used_names = mkUsedNames tc_result
dep_files <- (readIORef (tcg_dependent_files tc_result))
+ dep_dirs <- (readIORef (tcg_dependent_dirs tc_result))
(needed_links, needed_pkgs) <- readIORef (tcg_th_needed_deps tc_result)
let uc = initUsageConfig hsc_env
plugins = hsc_plugins hsc_env
@@ -289,6 +290,7 @@ mkRecompUsageInfo hsc_env tc_result = do
(tcg_import_decls tc_result)
used_names
dep_files
+ dep_dirs
(tcg_merged tc_result)
needed_links
needed_pkgs
=====================================
compiler/GHC/Iface/Recomp.hs
=====================================
@@ -194,6 +194,7 @@ data RecompReason
| ModuleChangedRaw ModuleName
| ModuleChangedIface ModuleName
| FileChanged FilePath
+ | DirChanged FilePath
| CustomReason String
| FlagsChanged
| LinkFlagsChanged
@@ -230,6 +231,7 @@ instance Outputable RecompReason where
ModuleRemoved (_st, _uid, m) -> ppr m <+> text "removed"
ModuleAdded (_st, _uid, m) -> ppr m <+> text "added"
FileChanged fp -> text fp <+> text "changed"
+ DirChanged dp -> text dp <+> text "changed"
CustomReason s -> text s
FlagsChanged -> text "Flags changed"
LinkFlagsChanged -> text "Flags changed"
@@ -815,6 +817,22 @@ checkModUsage fc UsageFile{ usg_file_path = file,
then \e -> pprTrace "UsageFile" (text (show e)) $ return recomp
else \_ -> return recomp -- if we can't find the file, just recompile, don't fail
+checkModUsage fc UsageDirectory{ usg_dir_path = dir,
+ usg_dir_hash = old_hash,
+ usg_dir_label = mlabel } =
+ liftIO $
+ handleIO handler $ do
+ new_hash <- lookupDirCache fc $ unpackFS dir
+ if (old_hash /= new_hash)
+ then return recomp
+ else return UpToDate
+ where
+ reason = DirChanged $ unpackFS dir
+ recomp = needsRecompileBecause $ fromMaybe reason $ fmap CustomReason mlabel
+ handler = if debugIsOn
+ then \e -> pprTrace "UsageDirectory" (text (show e)) $ return recomp
+ else \_ -> return recomp -- if we can't find the dir, just recompile, don't fail
+
-- | We are importing a module whose exports have changed.
-- Does this require recompilation?
--
=====================================
compiler/GHC/Iface/Recomp/Types.hs
=====================================
@@ -140,6 +140,10 @@ pprUsage usage@UsageFile{}
= hsep [text "addDependentFile",
doubleQuotes (ftext (usg_file_path usage)),
ppr (usg_file_hash usage)]
+pprUsage usage@UsageDirectory{}
+ = hsep [text "AddDependentDirectory",
+ doubleQuotes (ftext (usg_dir_path usage)),
+ ppr (usg_dir_hash usage)]
pprUsage usage@UsageMergedRequirement{}
= hsep [text "merged", ppr (usg_mod usage), ppr (usg_mod_hash usage)]
pprUsage usage@UsageHomeModuleInterface{}
=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -173,8 +173,6 @@ import GHC.Parser.HaddockLex (lexHsDoc)
import GHC.Parser (parseIdentifier)
import GHC.Rename.Doc (rnHsDoc)
-
-
{-
Note [Template Haskell state diagram]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -1524,6 +1522,11 @@ instance TH.Quasi TcM where
dep_files <- readTcRef ref
writeTcRef ref (fp:dep_files)
+ qAddDependentDirectory dp = do
+ ref <- fmap tcg_dependent_dirs getGblEnv
+ dep_dirs <- readTcRef ref
+ writeTcRef ref (dp:dep_dirs)
+
qAddTempFile suffix = do
dflags <- getDynFlags
logger <- getLogger
@@ -1928,6 +1931,7 @@ handleTHMessage msg = case msg of
ReifyConStrictness nm -> wrapTHResult $ TH.qReifyConStrictness nm
GetPackageRoot -> wrapTHResult $ TH.qGetPackageRoot
AddDependentFile f -> wrapTHResult $ TH.qAddDependentFile f
+ AddDependentDirectory d -> wrapTHResult $ TH.qAddDependentDirectory d
AddTempFile s -> wrapTHResult $ TH.qAddTempFile s
AddModFinalizer r -> do
interp <- hscInterp <$> getTopEnv
=====================================
compiler/GHC/Tc/Types.hs
=====================================
@@ -603,6 +603,7 @@ data TcGblEnv
-- decls.
tcg_dependent_files :: TcRef [FilePath], -- ^ dependencies from addDependentFile
+ tcg_dependent_dirs :: TcRef [FilePath], -- ^ dependencies from addDependentDirectory
tcg_th_topdecls :: TcRef [LHsDecl GhcPs],
-- ^ Top-level declarations from addTopDecls
=====================================
compiler/GHC/Tc/Utils/Monad.hs
=====================================
@@ -55,7 +55,7 @@ module GHC.Tc.Utils.Monad(
getRdrEnvs, getImports,
getFixityEnv, extendFixityEnv,
getDeclaredDefaultTys,
- addDependentFiles,
+ addDependentFiles, addDependentDirectories,
-- * Error management
getSrcSpanM, setSrcSpan, setSrcSpanA, addLocM,
@@ -274,6 +274,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
let { type_env_var = hsc_type_env_vars hsc_env };
dependent_files_var <- newIORef [] ;
+ dependent_dirs_var <- newIORef [] ;
static_wc_var <- newIORef emptyWC ;
cc_st_var <- newIORef newCostCentreState ;
th_topdecls_var <- newIORef [] ;
@@ -369,6 +370,7 @@ initTc hsc_env hsc_src keep_rn_syntax mod loc do_this
tcg_safe_infer = infer_var,
tcg_safe_infer_reasons = infer_reasons_var,
tcg_dependent_files = dependent_files_var,
+ tcg_dependent_dirs = dependent_dirs_var,
tcg_tc_plugin_solvers = [],
tcg_tc_plugin_rewriters = emptyUFM,
tcg_defaulting_plugins = [],
@@ -957,6 +959,12 @@ addDependentFiles fs = do
dep_files <- readTcRef ref
writeTcRef ref (fs ++ dep_files)
+addDependentDirectories :: [FilePath] -> TcRn ()
+addDependentDirectories ds = do
+ ref <- fmap tcg_dependent_dirs getGblEnv
+ dep_dirs <- readTcRef ref
+ writeTcRef ref (ds ++ dep_dirs)
+
{-
************************************************************************
* *
=====================================
compiler/GHC/Unit/Finder.hs
=====================================
@@ -31,6 +31,9 @@ module GHC.Unit.Finder (
findObjectLinkableMaybe,
findObjectLinkable,
+
+ -- important that GHC.HsToCore.Usage uses the same hashing method for usage dirs as is used here.
+ getDirHash,
) where
import GHC.Prelude
@@ -68,7 +71,9 @@ import qualified Data.Map as M
import GHC.Driver.Env
import GHC.Driver.Config.Finder
import qualified Data.Set as Set
+import qualified Data.List as L(sort)
import Data.List.NonEmpty ( NonEmpty (..) )
+import qualified System.Directory as SD
import qualified System.OsPath as OsPath
import qualified Data.List.NonEmpty as NE
@@ -107,10 +112,12 @@ initFinderCache :: IO FinderCache
initFinderCache = do
mod_cache <- newIORef emptyInstalledModuleEnv
file_cache <- newIORef M.empty
+ dir_cache <- newIORef M.empty
let flushFinderCaches :: UnitEnv -> IO ()
flushFinderCaches ue = do
atomicModifyIORef' mod_cache $ \fm -> (filterInstalledModuleEnv is_ext fm, ())
atomicModifyIORef' file_cache $ \_ -> (M.empty, ())
+ atomicModifyIORef' dir_cache $ \_ -> (M.empty, ())
where
is_ext mod _ = not (isUnitEnvInstalledModule ue mod)
@@ -137,8 +144,29 @@ initFinderCache = do
atomicModifyIORef' file_cache $ \c -> (M.insert key hash c, ())
return hash
Just fp -> return fp
+ lookupDirCache :: FilePath -> IO Fingerprint
+ lookupDirCache key = do
+ c <- readIORef dir_cache
+ case M.lookup key c of
+ Nothing -> do
+ hash <- getDirHash key
+ atomicModifyIORef' dir_cache $ \c -> (M.insert key hash c, ())
+ return hash
+ Just fp -> return fp
return FinderCache{..}
+-- | This function computes a shallow hash of a directory, so really just what files and directories are directly inside it.
+-- It does not look at the contents of the files, or the contents of the directories it contains.
+getDirHash :: FilePath -> IO Fingerprint
+getDirHash dir = do
+ contents <- SD.listDirectory dir
+ -- The documentation of Fingerprints describes this as an easy naive implementation
+ -- I wonder if we should do something more sophisticated here?
+ let hashes = fingerprintString <$> contents
+ let s_hashes = L.sort hashes
+ let hash = fingerprintFingerprints s_hashes
+ return hash
+
-- -----------------------------------------------------------------------------
-- The three external entry points
=====================================
compiler/GHC/Unit/Finder/Types.hs
=====================================
@@ -37,6 +37,7 @@ data FinderCache = FinderCache { flushFinderCaches :: UnitEnv -> IO ()
, lookupFileCache :: FilePath -> IO Fingerprint
-- ^ Look for the hash of a file in the cache. This should add it to the
-- cache. If the file doesn't exist, raise an IOException.
+ , lookupDirCache :: FilePath -> IO Fingerprint
}
data InstalledFindResult
=====================================
compiler/GHC/Unit/Module/Deps.hs
=====================================
@@ -357,6 +357,23 @@ data Usage
-- contents don't change. This previously lead to odd
-- recompilation behaviors; see #8114
}
+ | UsageDirectory {
+ usg_dir_path :: FastString,
+ -- ^ External dir dependency. From TH addDependentFile.
+ -- Should be absolute.
+ usg_dir_hash :: Fingerprint,
+ -- ^ 'Fingerprint' of the directories contents.
+
+ usg_dir_label :: Maybe String
+ -- ^ An optional string which is used in recompilation messages if
+ -- dir in question has changed.
+
+ -- Note: We do a very shallow check indeed, just what the contents of
+ -- the directory are, aka what files and directories are within it.
+ -- If those files/directories have their own contents changed...
+ -- We won't spot it here, better recursive add them to your usage
+ -- seperately.
+ }
| UsageHomeModuleInterface {
usg_mod_name :: ModuleName
-- ^ Name of the module
@@ -395,6 +412,7 @@ instance NFData Usage where
rnf (UsagePackageModule mod hash safe) = rnf mod `seq` rnf hash `seq` rnf safe `seq` ()
rnf (UsageHomeModule mod uid hash entities exports safe) = rnf mod `seq` rnf uid `seq` rnf hash `seq` rnf entities `seq` rnf exports `seq` rnf safe `seq` ()
rnf (UsageFile file hash label) = rnf file `seq` rnf hash `seq` rnf label `seq` ()
+ rnf (UsageDirectory dir hash label) = rnf dir `seq` rnf hash `seq` rnf label `seq` ()
rnf (UsageMergedRequirement mod hash) = rnf mod `seq` rnf hash `seq` ()
rnf (UsageHomeModuleInterface mod uid hash) = rnf mod `seq` rnf uid `seq` rnf hash `seq` ()
@@ -431,6 +449,12 @@ instance Binary Usage where
put_ bh (usg_unit_id usg)
put_ bh (usg_iface_hash usg)
+ put_ bh usg@UsageDirectory{} = do
+ putByte bh 5
+ put_ bh (usg_dir_path usg)
+ put_ bh (usg_dir_hash usg)
+ put_ bh (usg_dir_label usg)
+
get bh = do
h <- getByte bh
case h of
@@ -462,6 +486,12 @@ instance Binary Usage where
uid <- get bh
hash <- get bh
return UsageHomeModuleInterface { usg_mod_name = mod, usg_unit_id = uid, usg_iface_hash = hash }
+ 5 -> do
+ dp <- get bh
+ hash <- get bh
+ label <- get bh
+ return UsageDirectory { usg_dir_path = dp, usg_dir_hash = hash, usg_dir_label = label }
+
i -> error ("Binary.get(Usage): " ++ show i)
-- | Records the imports that we depend on from a home module,
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -232,6 +232,11 @@ Cmm
They are replaced, respectively, by ``SpecialiseEP``, ``pragSpecED`` and
``pragSpecInlED``.
+- We have added the ``addDependentDirectory`` function to match
+ ``addDependentFile``, which adds a directory to the list of dependencies that
+ the recompilation checker will look at to determine if a module needs to be
+ recompiled.
+
Included libraries
~~~~~~~~~~~~~~~~~~
=====================================
docs/users_guide/separate_compilation.rst
=====================================
@@ -710,7 +710,7 @@ beautiful sight!
You can read about :ghc-wiki:`how all this works <commentary/compiler/recompilation-avoidance>` in the GHC commentary.
Recompilation for Template Haskell and Plugins
-^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Recompilation checking gets a bit more complicated when using Template Haskell or
plugins. Both these features execute code at compile time and so if any of the
@@ -727,6 +727,19 @@ if ``foo`` is from module ``A`` and ``bar`` is from module ``B``, the module wil
now depend on ``A.o`` and ``B.o``, if either of these change then the module will
be recompiled.
+``addDependentFile`` and ``addDependentDirectory``
+^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
+
+When using Template Haskell or plugins, you can use the functions
+``addDependentFile`` and ``addDependentDirectory`` to add additional
+dependencies to the module being compiled.
+
+- When adding a file, this means that the contents of the file changing between
+ compilations will trigger a recompilation of the module.
+- When adding a directory, this means that any file or subdirectory *added* to or
+ *removed* from the directory will trigger recompilation of the module, so
+ it is not a recursive dependency.
+
.. _mutual-recursion:
Mutually recursive modules and hs-boot files
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs
=====================================
@@ -135,6 +135,9 @@ class (MonadIO m, MonadFail m) => Quasi m where
-- | See 'addDependentFile'.
qAddDependentFile :: FilePath -> m ()
+ -- | See 'addDependentDirectory'.
+ qAddDependentDirectory :: FilePath -> m ()
+
-- | See 'addTempFile'.
qAddTempFile :: String -> m FilePath
@@ -181,30 +184,31 @@ instance Quasi IO where
qReport True msg = hPutStrLn stderr ("Template Haskell error: " ++ msg)
qReport False msg = hPutStrLn stderr ("Template Haskell error: " ++ msg)
- qLookupName _ _ = badIO "lookupName"
- qReify _ = badIO "reify"
- qReifyFixity _ = badIO "reifyFixity"
- qReifyType _ = badIO "reifyFixity"
- qReifyInstances _ _ = badIO "reifyInstances"
- qReifyRoles _ = badIO "reifyRoles"
- qReifyAnnotations _ = badIO "reifyAnnotations"
- qReifyModule _ = badIO "reifyModule"
- qReifyConStrictness _ = badIO "reifyConStrictness"
- qLocation = badIO "currentLocation"
- qRecover _ _ = badIO "recover" -- Maybe we could fix this?
- qGetPackageRoot = badIO "getProjectRoot"
- qAddDependentFile _ = badIO "addDependentFile"
- qAddTempFile _ = badIO "addTempFile"
- qAddTopDecls _ = badIO "addTopDecls"
- qAddForeignFilePath _ _ = badIO "addForeignFilePath"
- qAddModFinalizer _ = badIO "addModFinalizer"
- qAddCorePlugin _ = badIO "addCorePlugin"
- qGetQ = badIO "getQ"
- qPutQ _ = badIO "putQ"
- qIsExtEnabled _ = badIO "isExtEnabled"
- qExtsEnabled = badIO "extsEnabled"
- qPutDoc _ _ = badIO "putDoc"
- qGetDoc _ = badIO "getDoc"
+ qLookupName _ _ = badIO "lookupName"
+ qReify _ = badIO "reify"
+ qReifyFixity _ = badIO "reifyFixity"
+ qReifyType _ = badIO "reifyFixity"
+ qReifyInstances _ _ = badIO "reifyInstances"
+ qReifyRoles _ = badIO "reifyRoles"
+ qReifyAnnotations _ = badIO "reifyAnnotations"
+ qReifyModule _ = badIO "reifyModule"
+ qReifyConStrictness _ = badIO "reifyConStrictness"
+ qLocation = badIO "currentLocation"
+ qRecover _ _ = badIO "recover" -- Maybe we could fix this?
+ qGetPackageRoot = badIO "getProjectRoot"
+ qAddDependentFile _ = badIO "addDependentFile"
+ qAddDependentDirectory _ = badIO "AddDependentDirectory"
+ qAddTempFile _ = badIO "addTempFile"
+ qAddTopDecls _ = badIO "addTopDecls"
+ qAddForeignFilePath _ _ = badIO "addForeignFilePath"
+ qAddModFinalizer _ = badIO "addModFinalizer"
+ qAddCorePlugin _ = badIO "addCorePlugin"
+ qGetQ = badIO "getQ"
+ qPutQ _ = badIO "putQ"
+ qIsExtEnabled _ = badIO "isExtEnabled"
+ qExtsEnabled = badIO "extsEnabled"
+ qPutDoc _ _ = badIO "putDoc"
+ qGetDoc _ = badIO "getDoc"
instance Quote IO where
newName = newNameIO
@@ -822,6 +826,26 @@ getPackageRoot :: Q FilePath
getPackageRoot = Q qGetPackageRoot
+-- | Record external directories that runIO is using (dependent upon).
+-- The compiler can then recognize that it should re-compile the Haskell file
+-- when a directory changes.
+--
+-- Expects an absolute directory path.
+--
+-- Notes:
+--
+-- * ghc -M does not know about these dependencies - it does not execute TH.
+--
+-- * The dependency is shallow, based only on the direct content.
+-- Basically, it only sees a list of names. It does not look at directory
+-- metadata, recurse into subdirectories, or look at file contents. As
+-- long as the list of names remains the same, the directory is considered
+-- unchanged.
+--
+-- * The state of the directory is read at the interface generation time,
+-- not at the time of the function call.
+addDependentDirectory :: FilePath -> Q ()
+addDependentDirectory dp = Q (qAddDependentDirectory dp)
-- | Record external files that runIO is using (dependent upon).
-- The compiler can then recognize that it should re-compile the Haskell file
@@ -833,7 +857,11 @@ getPackageRoot = Q qGetPackageRoot
--
-- * ghc -M does not know about these dependencies - it does not execute TH.
--
--- * The dependency is based on file content, not a modification time
+-- * The dependency is based on file content, not a modification time or
+-- any other metadata associated with the file (e.g. permissions).
+--
+-- * The state of the file is read at the interface generation time,
+-- not at the time of the function call.
addDependentFile :: FilePath -> Q ()
addDependentFile fp = Q (qAddDependentFile fp)
@@ -961,32 +989,33 @@ instance MonadIO Q where
liftIO = runIO
instance Quasi Q where
- qNewName = newName
- qReport = report
- qRecover = recover
- qReify = reify
- qReifyFixity = reifyFixity
- qReifyType = reifyType
- qReifyInstances = reifyInstances
- qReifyRoles = reifyRoles
- qReifyAnnotations = reifyAnnotations
- qReifyModule = reifyModule
- qReifyConStrictness = reifyConStrictness
- qLookupName = lookupName
- qLocation = location
- qGetPackageRoot = getPackageRoot
- qAddDependentFile = addDependentFile
- qAddTempFile = addTempFile
- qAddTopDecls = addTopDecls
- qAddForeignFilePath = addForeignFilePath
- qAddModFinalizer = addModFinalizer
- qAddCorePlugin = addCorePlugin
- qGetQ = getQ
- qPutQ = putQ
- qIsExtEnabled = isExtEnabled
- qExtsEnabled = extsEnabled
- qPutDoc = putDoc
- qGetDoc = getDoc
+ qNewName = newName
+ qReport = report
+ qRecover = recover
+ qReify = reify
+ qReifyFixity = reifyFixity
+ qReifyType = reifyType
+ qReifyInstances = reifyInstances
+ qReifyRoles = reifyRoles
+ qReifyAnnotations = reifyAnnotations
+ qReifyModule = reifyModule
+ qReifyConStrictness = reifyConStrictness
+ qLookupName = lookupName
+ qLocation = location
+ qGetPackageRoot = getPackageRoot
+ qAddDependentFile = addDependentFile
+ qAddDependentDirectory = addDependentDirectory
+ qAddTempFile = addTempFile
+ qAddTopDecls = addTopDecls
+ qAddForeignFilePath = addForeignFilePath
+ qAddModFinalizer = addModFinalizer
+ qAddCorePlugin = addCorePlugin
+ qGetQ = getQ
+ qPutQ = putQ
+ qIsExtEnabled = isExtEnabled
+ qExtsEnabled = extsEnabled
+ qPutDoc = putDoc
+ qGetDoc = getDoc
----------------------------------------------------
=====================================
libraries/ghci/GHCi/Message.hs
=====================================
@@ -291,6 +291,7 @@ data THMessage a where
GetPackageRoot :: THMessage (THResult FilePath)
AddDependentFile :: FilePath -> THMessage (THResult ())
+ AddDependentDirectory :: FilePath -> THMessage (THResult ())
AddTempFile :: String -> THMessage (THResult FilePath)
AddModFinalizer :: RemoteRef (TH.Q ()) -> THMessage (THResult ())
AddCorePlugin :: String -> THMessage (THResult ())
@@ -343,6 +344,7 @@ getTHMessage = do
23 -> THMsg <$> (PutDoc <$> get <*> get)
24 -> THMsg <$> GetDoc <$> get
25 -> THMsg <$> return GetPackageRoot
+ 26 -> THMsg <$> AddDependentDirectory <$> get
n -> error ("getTHMessage: unknown message " ++ show n)
putTHMessage :: THMessage a -> Put
@@ -373,7 +375,7 @@ putTHMessage m = case m of
PutDoc l s -> putWord8 23 >> put l >> put s
GetDoc l -> putWord8 24 >> put l
GetPackageRoot -> putWord8 25
-
+ AddDependentDirectory a -> putWord8 26 >> put a
data EvalOpts = EvalOpts
{ useSandboxThread :: Bool
=====================================
libraries/ghci/GHCi/TH.hs
=====================================
@@ -198,6 +198,7 @@ instance TH.Quasi GHCiQ where
qLocation = fromMaybe noLoc . qsLocation <$> getState
qGetPackageRoot = ghcCmd GetPackageRoot
qAddDependentFile file = ghcCmd (AddDependentFile file)
+ qAddDependentDirectory dir = ghcCmd (AddDependentDirectory dir)
qAddTempFile suffix = ghcCmd (AddTempFile suffix)
qAddTopDecls decls = ghcCmd (AddTopDecls decls)
qAddForeignFilePath lang fp = ghcCmd (AddForeignFilePath lang fp)
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -32,6 +32,7 @@ module Language.Haskell.TH.Syntax (
ModName (..),
addCorePlugin,
addDependentFile,
+ addDependentDirectory,
addForeignFile,
addForeignFilePath,
addForeignSource,
=====================================
testsuite/.gitignore
=====================================
@@ -1523,6 +1523,7 @@ mk/ghcconfig*_test___spaces_ghc*.exe.mk
/tests/th/T8633
/tests/th/TH_Depends
/tests/th/TH_Depends_external.txt
+/tests/th/TH_Depends_external/dummy.txt
/tests/th/TH_StringPrimL
/tests/th/TH_import_loop/ModuleA.hi-boot
/tests/th/TH_import_loop/ModuleA.o-boot
=====================================
testsuite/tests/interface-stability/template-haskell-exports.stdout
=====================================
@@ -1715,6 +1715,7 @@ module Language.Haskell.TH.Syntax where
qRunIO :: forall a. GHC.Internal.Types.IO a -> m a
qGetPackageRoot :: m GHC.Internal.IO.FilePath
qAddDependentFile :: GHC.Internal.IO.FilePath -> m ()
+ qAddDependentDirectory :: GHC.Internal.IO.FilePath -> m ()
qAddTempFile :: GHC.Internal.Base.String -> m GHC.Internal.IO.FilePath
qAddTopDecls :: [Dec] -> m ()
qAddForeignFilePath :: ForeignSrcLang -> GHC.Internal.Base.String -> m ()
@@ -1726,7 +1727,7 @@ module Language.Haskell.TH.Syntax where
qExtsEnabled :: m [Extension]
qPutDoc :: DocLoc -> GHC.Internal.Base.String -> m ()
qGetDoc :: DocLoc -> m (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
- {-# MINIMAL qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc #-}
+ {-# MINIMAL qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddDependentDirectory, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc #-}
type Quote :: (* -> *) -> Constraint
class GHC.Internal.Base.Monad m => Quote m where
newName :: GHC.Internal.Base.String -> m Name
@@ -1779,6 +1780,7 @@ module Language.Haskell.TH.Syntax where
type VarStrictType :: *
type VarStrictType = VarBangType
addCorePlugin :: GHC.Internal.Base.String -> Q ()
+ addDependentDirectory :: GHC.Internal.IO.FilePath -> Q ()
addDependentFile :: GHC.Internal.IO.FilePath -> Q ()
addForeignFile :: ForeignSrcLang -> GHC.Internal.Base.String -> Q ()
addForeignFilePath :: ForeignSrcLang -> GHC.Internal.IO.FilePath -> Q ()
=====================================
testsuite/tests/th/Makefile
=====================================
@@ -43,6 +43,20 @@ TH_Depends:
'$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends
./TH_Depends
+.PHONY: TH_Depends_Dir
+TH_Depends_Dir:
+ rm -rf TH_Depends_external
+ $(RM) TH_Depends_Dir TH_Depends_Dir.exe
+ $(RM) TH_Depends_Dir.o TH_Depends_Dir.hi
+ $(RM) TH_Depends_Dir_External.o TH_Depends_Dir_External.hi
+
+ mkdir TH_Depends_external
+ '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir
+ ./TH_Depends_Dir
+ sleep 2
+ echo "dummy" > TH_Depends_external/dummy.txt
+ '$(TEST_HC)' $(TEST_HC_OPTS) $(ghcThWayFlags) --make -v0 TH_Depends_Dir
+ ./TH_Depends_Dir
T8333:
'$(TEST_HC)' $(TEST_HC_OPTS_INTERACTIVE) $(ghcThWayFlags) T8333.hs < /dev/null
=====================================
testsuite/tests/th/TH_Depends_Dir.hs
=====================================
@@ -0,0 +1,9 @@
+
+{-# LANGUAGE TemplateHaskell #-}
+
+module Main where
+
+import TH_Depends_Dir_External (checkDirectoryContent)
+
+main :: IO ()
+main = putStrLn $checkDirectoryContent
\ No newline at end of file
=====================================
testsuite/tests/th/TH_Depends_Dir.stdout
=====================================
@@ -0,0 +1,2 @@
+no files?
+yes files!
\ No newline at end of file
=====================================
testsuite/tests/th/TH_Depends_Dir_External.hs
=====================================
@@ -0,0 +1,15 @@
+
+module TH_Depends_Dir_External where
+
+import Language.Haskell.TH.Syntax
+import Language.Haskell.TH.Lib
+import System.Directory (listDirectory)
+
+checkDirectoryContent :: Q Exp
+checkDirectoryContent = do
+ qAddDependentDirectory "TH_Depends_external"
+ l <- qRunIO $ listDirectory "TH_Depends_external"
+ let s = case l of
+ [] -> "no files?"
+ _ -> "yes files!"
+ stringE s
\ No newline at end of file
=====================================
testsuite/tests/th/all.T
=====================================
@@ -214,6 +214,7 @@ test('T5434', [], multimod_compile,
['T5434', '-v0 -Wall ' + config.ghc_th_way_flags])
test('T5508', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('TH_Depends', [only_ways(['normal'])], makefile_test, ['TH_Depends'])
+test('TH_Depends_Dir', [only_ways(['normal'])], makefile_test, ['TH_Depends_Dir'])
test('T5597', [], multimod_compile, ['T5597', '-v0 ' + config.ghc_th_way_flags])
test('T5665', [], multimod_compile, ['T5665', '-v0 ' + config.ghc_th_way_flags])
test('T5700', [], multimod_compile,
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/43229cd960b8bcb6476073d57a8c706…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/43229cd960b8bcb6476073d57a8c706…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/T25944] 187 commits: Add name for -Wunusable-unpack-pragmas
by Sebastian Graf (@sgraf812) 14 Jul '25
by Sebastian Graf (@sgraf812) 14 Jul '25
14 Jul '25
Sebastian Graf pushed to branch wip/T25944 at Glasgow Haskell Compiler / GHC
Commits:
e2f2f9d0 by Vladislav Zavialov at 2025-04-20T10:53:39-04:00
Add name for -Wunusable-unpack-pragmas
This warning had no name or flag and was triggered unconditionally.
Now it is part of -Wdefault.
In GHC.Tc.TyCl.tcTyClGroupsPass's strict mode, we now have to
force-enable this warning to ensure that detection of flawed groups
continues to work even if the user disables the warning with the
-Wno-unusable-unpack-pragmas option. Test case: T3990c
Also, the misnamed BackpackUnpackAbstractType is now called
UnusableUnpackPragma.
- - - - -
6caa6508 by Adam Gundry at 2025-04-20T10:54:22-04:00
Fix specialisation of incoherent instances (fixes #25883)
GHC normally assumes that class constraints are canonical, meaning that
the specialiser is allowed to replace one dictionary argument with another
provided that they have the same type. The `-fno-specialise-incoherents`
flag alters INCOHERENT instance definitions so that they will prevent
specialisation in some cases, by inserting `nospec`.
This commit fixes a bug in 7124e4ad76d98f1fc246ada4fd7bf64413ff2f2e, which
treated some INCOHERENT instance matches as if `-fno-specialise-incoherents`
was in effect, thereby unnecessarily preventing specialisation. In addition
it updates the relevant `Note [Rules for instance lookup]` and adds a new
`Note [Canonicity for incoherent matches]`.
- - - - -
0426fd6c by Adam Gundry at 2025-04-20T10:54:23-04:00
Add regression test for #23429
- - - - -
eec96527 by Adam Gundry at 2025-04-20T10:54:23-04:00
user's guide: update specification of overlapping/incoherent instances
The description of the instance resolution algorithm in the user's
guide was slightly out of date, because it mentioned in-scope given
constraints only at the end, whereas the implementation checks for
their presence before any of the other steps.
This also adds a warning to the user's guide about the impact of
incoherent instances on specialisation, and more clearly documents
some of the other effects of `-XIncoherentInstances`.
- - - - -
a00eeaec by Matthew Craven at 2025-04-20T10:55:03-04:00
Fix bytecode generation for `tagToEnum# <LITERAL>`
Fixes #25975.
- - - - -
2e204269 by Andreas Klebinger at 2025-04-22T12:20:41+02:00
Simplifier: Constant fold invald tagToEnum# calls to bottom expr.
When applying tagToEnum# to a out-of-range value it's best to simply
constant fold it to a bottom expression. That potentially allows more
dead code elimination and makes debugging easier.
Fixes #25976
- - - - -
7250fc0c by Matthew Pickering at 2025-04-22T16:24:04-04:00
Move -fno-code note into Downsweep module
This note was left behind when all the code which referred to it was
moved into the GHC.Driver.Downsweep module
- - - - -
d2dc89b4 by Matthew Pickering at 2025-04-22T16:24:04-04:00
Apply editing notes to Note [-fno-code mode] suggested by sheaf
These notes were suggested in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/14241
- - - - -
91564daf by Matthew Pickering at 2025-04-24T00:29:02-04:00
ghci: Use loadInterfaceForModule rather than loadSrcInterface in mkTopLevEnv
loadSrcInterface takes a user given `ModuleName` and resolves it to the
module which needs to be loaded (taking into account module
renaming/visibility etc).
loadInterfaceForModule takes a specific module and loads it.
The modules in `ImpDeclSpec` have already been resolved to the actual
module to get the information from during renaming. Therefore we just
need to fetch the precise interface from disk (and not attempt to rename
it again).
Fixes #25951
- - - - -
2e0c07ab by Simon Peyton Jones at 2025-04-24T00:29:43-04:00
Test for #23298
- - - - -
0eef99b0 by Sven Tennie at 2025-04-24T07:34:36-04: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.
- - - - -
1bd3d13e by fendor at 2025-04-24T07:35:17-04:00
Add `UnitId` to `EvalBreakpoint`
The `EvalBreakpoint` is used to communicate that a breakpoint was
encountered during code evaluation.
This `EvalBreakpoint` needs to be converted to an `InternalBreakpointId`
which stores a `Module` to uniquely find the correct `Module` in the
Home Package Table.
The `EvalBreakpoint` used to store only a `ModuleName` which is then
converted to a `Module` based on the currently active home unit.
This is incorrect in the face of multiple home units, the break point
could be in an entirely other home unit!
To fix this, we additionally store the `UnitId` of the `Module` in
`EvalBreakpoint` to later reconstruct the correct `Module`
All of the changes are the consequence of extending `EvalBreakpoint`
with the additional `ShortByteString` of the `UnitId`.
For performance reasons, we store the `ShortByteString` backing the
`UnitId` directly, avoiding marshalling overhead.
- - - - -
fe6ed8d9 by Sylvain Henry at 2025-04-24T18:04:12-04:00
Doc: add doc for JS interruptible calling convention (#24444)
- - - - -
6111c5e4 by Ben Gamari at 2025-04-24T18:04:53-04:00
compiler: Ensure that Panic.Plain.assertPanic' provides callstack
In 36cddd2ce1a3bc62ea8a1307d8bc6006d54109cf @alt-romes removed CallStack
output from `GHC.Utils.Panic.Plain.assertPanic'`. While this output is
redundant due to the exception backtrace proposal, we may be
bootstrapping with a compiler which does not yet include this machinery.
Reintroduce the output for now.
Fixes #25898.
- - - - -
217caad1 by Matthew Pickering at 2025-04-25T18:58:42+01:00
Implement Explicit Level Imports for Template Haskell
This commit introduces the `ExplicitLevelImports` and
`ImplicitStagePersistence` language extensions as proposed in GHC
Proposal #682.
Key Features
------------
- `ExplicitLevelImports` adds two new import modifiers - `splice` and
`quote` - allowing precise control over the level at which imported
identifiers are available
- `ImplicitStagePersistence` (enabled by default) preserves existing
path-based cross-stage persistence behavior
- `NoImplicitStagePersistence` disables implicit cross-stage
persistence, requiring explicit level imports
Benefits
--------
- Improved compilation performance by reducing unnecessary code generation
- Enhanced IDE experience with faster feedback in `-fno-code` mode
- Better dependency tracking by distinguishing compile-time and runtime dependencies
- Foundation for future cross-compilation improvements
This implementation enables the separation of modules needed at
compile-time from those needed at runtime, allowing for more efficient
compilation pipelines and clearer code organization in projects using
Template Haskell.
Implementation Notes
--------------------
The level which a name is availble at is stored in the 'GRE', in the normal
GlobalRdrEnv. The function `greLevels` returns the levels which a specific GRE
is imported at. The level information for a 'Name' is computed by `getCurrentAndBindLevel`.
The level validity is checked by `checkCrossLevelLifting`.
Instances are checked by `checkWellLevelledDFun`, which computes the level an
instance by calling `checkWellLevelledInstanceWhat`, which sees what is
available at by looking at the module graph.
Modifications to downsweep
--------------------------
Code generation is now only enabled for modules which are needed at
compile time.
See the Note [-fno-code mode] for more information.
Uniform error messages for level errors
---------------------------------------
All error messages to do with levels are now reported uniformly using
the `TcRnBadlyStaged` constructor.
Error messages are uniformly reported in terms of levels.
0 - top-level
1 - quote level
-1 - splice level
The only level hard-coded into the compiler is the top-level in
GHC.Types.ThLevelIndex.topLevelIndex.
Uniformly refer to levels and stages
------------------------------------
There was much confusion about levels vs stages in the compiler.
A level is a semantic concept, used by the typechecker to ensure a
program can be evaluated in a well-staged manner.
A stage is an operational construct, program evaluation proceeds in
stages.
Deprecate -Wbadly-staged-types
------------------------------
`-Wbadly-staged-types` is deprecated in favour of `-Wbadly-levelled-types`.
Lift derivation changed
-----------------------
Derived lift instances will now not generate code with expression
quotations.
Before:
```
data A = A Int deriving Lift
=>
lift (A x) = [| A $(lift x) |]
```
After:
```
lift (A x) = conE 'A `appE` (lift x)
```
This is because if you attempt to derive `Lift` in a module where
`NoImplicitStagePersistence` is enabled, you would get an infinite loop
where a constructor was attempted to be persisted using the instance you
are currently defining.
GHC API Changes
---------------
The ModuleGraph now contains additional information about the type of
the edges (normal, quote or splice) between modules. This is abstracted
using the `ModuleGraphEdge` data type.
Fixes #25828
-------------------------
Metric Increase:
MultiLayerModulesTH_Make
-------------------------
- - - - -
7641a74a by Simon Peyton Jones at 2025-04-26T22:05:19-04:00
Get a decent MatchContext for pattern synonym bindings
In particular when we have a pattern binding
K p1 .. pn = rhs
where K is a pattern synonym. (It might be nested.)
This small MR fixes #25995. It's a tiny fix, to an error message,
removing an always-dubious `unkSkol`.
The bug report was in the context of horde-ad, a big program,
and I didn't manage to make a small repro case quickly. I decided
not to bother further.
- - - - -
ce616f49 by Simon Peyton Jones at 2025-04-27T21:10:25+01:00
Fix infelicities in the Specialiser
On the way to #23109 (unary classes) I discovered some infelicities
(or maybe tiny bugs, I forget) in the type-class specialiser.
I also tripped over #25965, an outright bug in the rule matcher
Specifically:
* Refactor: I enhanced `wantCallsFor`, whih previously always said
`True`, to discard calls of class-ops, data constructors etc. This is
a bit more efficient; and it means we don't need to worry about
filtering them out later.
* Fix: I tidied up some tricky logic that eliminated redundant
specialisations. It wasn't working correctly. See the expanded
Note [Specialisations already covered], and
(MP3) in Note [Specialising polymorphic dictionaries].
See also the new top-level `alreadyCovered`
function, which now goes via `GHC.Core.Rules.ruleLhsIsMoreSpecific`
I also added a useful Note [The (CI-KEY) invariant]
* Fix #25965: fixed a tricky bug in the `go_fam_fam` in
`GHC.Core.Unify.uVarOrFam`, which allows matching to succeed
without binding all type varibles.
I enhanced Note [Apartness and type families] some more
* #25703. This ticket "just works" with -fpolymorphic-specialisation;
but I was surprised that it worked! In this MR I added documentation
to Note [Interesting dictionary arguments] to explain; and tests to
ensure it stays fixed.
- - - - -
22d11fa8 by Simon Peyton Jones at 2025-04-28T18:05:19-04:00
Track rewriter sets more accurately in constraint solving
The key change, which fixed #25440, is to call `recordRewriter` in
GHC.Tc.Solver.Rewrite.rewrite_exact_fam_app. This missing call meant
that we were secretly rewriting a Wanted with a Wanted, but not really
noticing; and that led to a very bad error message, as you can see
in the ticket.
But of course that led me into rabbit hole of other refactoring around
the RewriteSet code:
* Improve Notes [Wanteds rewrite Wanteds]
* Zonk the RewriterSet in `zonkCtEvidence` rather than only in GHC.Tc.Errors.
This is tidier anyway (e.g. de-clutters debug output), and helps with the
next point.
* In GHC.Tc.Solver.Equality.inertsCanDischarge, don't replace a constraint
with no rewriters with an equal constraint that has many. See
See (CE4) in Note [Combining equalities]
* Move zonkRewriterSet and friends from GHC.Tc.Zonk.Type into
GHC.Tc.Zonk.TcType, where they properly belong.
A handful of tests get better error messages.
For some reason T24984 gets 12% less compiler allocation -- good
Metric Decrease:
T24984
- - - - -
6467d61e by Brandon Chinn at 2025-04-29T18:36:03-04:00
Fix lexing "\^\" (#25937)
This broke in the refactor in !13128, where the old code parsed escape
codes and collapsed string gaps at the same time, but the new code
collapsed gaps first, then resolved escape codes. The new code used a
naive heuristic to skip escaped backslashes, but didn't account for
"\^\".
- - - - -
99868a86 by Jens Petersen at 2025-04-29T18:36:44-04:00
hadrian: default selftest to disabled
- - - - -
aba2a4a5 by Zubin Duggal at 2025-04-30T06:35:59-04:00
get-win32-tarballs.py: List tarball files to be downloaded if we cannot find them
Fixes #25929
- - - - -
d99a617b by Ben Gamari at 2025-04-30T06:36:40-04:00
Move Data ModuleName instance to Language.Haskell.Syntax.Module.Name
Fixes #25968.
- - - - -
9995c2b7 by Serge S. Gulin at 2025-05-04T17:13:36+03:00
Support for ARM64 Windows (LLVM-enabled) (fixes #24603)
1. Add Windows AArch64 cross-compilation support via CI jobs
Introduce new CI configurations for cross-compiling to Windows ARM64 using Debian12Wine, FEX, and MSYS2.
Configure toolchain variables for LLVM MinGW and Wine emulation in CI pipelines.
2. Adjust compiler and RTS for AArch64 Windows compatibility
Reserve register `x18` on Windows and Darwin platforms in AArch64 codegen.
Handle Windows-specific relocations and data sections in AArch64 assembler.
Update PEi386 linker to recognize ARM64 binaries and support exception handling.
Adjust LLVM target definitions and data layouts for new architectures.
Update `ghc-toolchain` and build scripts to handle `TablesNextToCode` on Windows ARM64.
3. Enhance CI scripts and stability
Modify `ci.sh` to handle mingw cross-targets, fixing GHC executable paths and test execution.
Use `diff -w` in tests to ignore whitespace differences, improving cross-platform consistency.
4. Refactor and clean up code
Remove redundant imports in hello.hs test.
Improve error messages and checks for unsupported configurations in the driver.
Add `EXDEV` error code to `errno.js`.
Add async/sync flags to IO logs at `base.js`.
Improve POSIX compatibility for file close at `base.js`: decrease indeterminism for mixed cases of async and sync code.
5. Update dependencies: `Cabal`, `Win32`, `directory`, `process`, `haskeline`, and `unix`.
submodule
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
Co-authored-by: Dmitrii Egorov <egorov.d.i(a)icloud.com>
Co-authored-by: Andrei Borzenkov <root(a)sandwitch.dev>
- - - - -
50fa8165 by Javran Cheng at 2025-05-05T05:55:39-04:00
Suppress unused do-binding if discarded variable is Any or ZonkAny.
Consider example (#25895):
> do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`.
Nothing constrains `b`, so it will be instantiates with `Any` or
`ZonkAny`.
But we certainly don't want to complain about a discarded do-binding.
Fixes #25895
- - - - -
e46c6b18 by Rodrigo Mesquita at 2025-05-06T09:01:57-04:00
Refactor mkTopLevImportedEnv out of mkTopLevEnv
This makes the code clearer and allows the top-level import context to
be fetched directly from the HomeModInfo through the API (e.g. useful
for the debugger).
- - - - -
0ce0d263 by Rodrigo Mesquita at 2025-05-06T09:01:57-04:00
Export sizeOccEnv from GHC.Types.Name.Occurrence
Counts the number of OccNames in an OccEnv
- - - - -
165f98d8 by Simon Peyton Jones at 2025-05-06T09:02:39-04:00
Fix a bad untouchability bug im simplifyInfer
This patch addresses #26004. The root cause was that simplifyInfer
was willing to unify variables "far out". The fix, in
runTcSWithEvBinds', is to initialise the inert set given-eq level with
the current level. See
(TGE6) in Note [Tracking Given equalities]
in GHC.Tc.Solver.InertSet
Two loosely related refactors:
* Refactored approximateWCX to return just the free type
variables of the un-quantified constraints. That avoids duplication
of work (these free vars are needed in simplifyInfer) and makes it
clearer that the constraints themselves are irrelevant.
* A little local refactor of TcSMode, which reduces the number of
parameters to runTcSWithEvBinds
- - - - -
6e67fa08 by Ben Gamari at 2025-05-08T06:21:21-04:00
llvmGen: Fix built-in variable predicate
Previously the predicate to identify LLVM builtin global variables was
checking for `$llvm` rather than `@llvm` as it should.
- - - - -
a9d0a22c by Ben Gamari at 2025-05-08T06:21:22-04:00
llvmGen: Fix linkage of built-in arrays
LLVM now insists that built-in arrays use Appending linkage, not
Internal.
Fixes #25769.
- - - - -
9c6d2b1b by sheaf at 2025-05-08T06:22:11-04:00
Use mkTrAppChecked in ds_ev_typeable
This change avoids violating the invariant of mkTrApp according to which
the argument should not be a fully saturated function type.
This ensures we don't return false negatives for type equality
involving function types.
Fixes #25998
- - - - -
75cadf81 by Ryan Hendrickson at 2025-05-08T06:22:55-04:00
haddock: Preserve indentation in multiline examples
Intended for use with :{ :}, but doesn't look for those characters. Any
consecutive lines with birdtracks will only have initial whitespace
stripped up to the column of the first line.
- - - - -
fee9b351 by Cheng Shao at 2025-05-08T06:23:36-04:00
ci: re-enable chrome for wasm ghci browser tests
Currently only firefox is enabled for wasm ghci browser tests, for
some reason testing with chrome works on my machine but gets stuck on
gitlab instance runners. This patch re-enables testing with chrome by
passing `--no-sandbox`, since chrome sandboxing doesn't work in
containers without `--cap-add=SYS_ADMIN`.
- - - - -
282df905 by Vladislav Zavialov at 2025-05-09T03:18:25-04:00
Take subordinate 'type' specifiers into account
This patch fixes multiple bugs (#22581, #25983, #25984, #25991)
in name resolution of subordinate import lists.
Bug #22581
----------
In subordinate import lists, the use of the `type` namespace specifier
used to be ignored. For example, this import statement was incorrectly
accepted:
import Prelude (Bool(type True))
Now it results in an error message:
<interactive>:2:17: error: [GHC-51433]
In the import of ‘Prelude’:
a data type called ‘Bool’ is exported,
but its subordinate item ‘True’ is not in the type namespace.
Bug #25983
----------
In subordinate import lists within a `hiding` clause, non-existent
items led to a poor warning message with -Wdodgy-imports. Consider:
import Prelude hiding (Bool(X))
The warning message for this import statement used to misreport the
cause of the problem:
<interactive>:3:24: warning: [GHC-56449] [-Wdodgy-imports]
In the import of ‘Prelude’:
an item called ‘Bool’ is exported, but it is a type.
Now the warning message is correct:
<interactive>:2:24: warning: [GHC-10237] [-Wdodgy-imports]
In the import of ‘Prelude’:
a data type called ‘Bool’ is exported, but it does not export
any constructors or record fields called ‘X’.
Bug #25984
----------
In subordinate import lists within a `hiding` clause, non-existent
items resulted in the entire import declaration being discarded.
For example, this program was incorrectly accepted:
import Prelude hiding (Bool(True,X))
t = True
Now it results in an error message:
<interactive>:2:5: error: [GHC-88464]
Data constructor not in scope: True
Bug #25991
----------
In subordinate import lists, it was not possible to refer to a class
method if there was an associated type of the same name:
module M_helper where
class C a b where
type a # b
(#) :: a -> b -> ()
module M where
import M_helper (C((#)))
This import declaration failed with:
M.hs:2:28: error: [GHC-10237]
In the import of ‘M_helper’:
an item called ‘C’ is exported, but it does not export any children
(constructors, class methods or field names) called ‘#’.
Now it is accepted.
Summary
-------
The changes required to fix these bugs are almost entirely confined to
GHC.Rename.Names. Other than that, there is a new error constructor
BadImportNonTypeSubordinates with error code [GHC-51433].
Test cases:
T22581a T22581b T22581c T22581d
T25983a T25983b T25983c T25983d T25983e T25983f T25983g
T25984a T25984b
T25991a T25991b1 T25991b2
- - - - -
51b0ce8f by Simon Peyton Jones at 2025-05-09T03:19:07-04:00
Slighty improve `dropMisleading`
Fix #26105, by upgrading the (horrible, hacky) `dropMisleading`
function.
This fix makes things a bit better but does not cure the underlying
problem.
- - - - -
7b2d1e6d by Simon Peyton Jones at 2025-05-11T03:24:47-04:00
Refine `noGivenNewtypeReprEqs` to account for quantified constraints
This little MR fixes #26020. We are on the edge of completeness
for newtype equalities (that doesn't change) but this MR makes GHC
a bit more consistent -- and fixes the bug reported.
- - - - -
eaa8093b by Cheng Shao at 2025-05-11T03:25:28-04:00
wasm: mark freeJSVal as INLINE
This patch marks `freeJSVal` as `INLINE` for the wasm backend. I
noticed that the `freeJSVal` invocations are not inlined when
inspecting STG/Cmm dumps of downstream libraries that use release
build of the wasm backend. The performance benefit of inlining here is
very modest, but so is the cost anyway; if you are using `freeJSVal`
at all then you care about every potential chance to improve
performance :)
- - - - -
eac196df by Cheng Shao at 2025-05-11T03:25:28-04:00
wasm: add zero length fast path for fromJSString
This patch adds a zero length fast path for `fromJSString`; when
marshaling a zero-length `JSString` we don't need to allocate an empty
`ByteArray#` at all.
- - - - -
652cba7e by Peng Fan at 2025-05-14T04:24:35-04:00
Add LoongArch NCG support
Not supported before.
- - - - -
c01f4374 by Lin Runze at 2025-05-14T04:24:35-04:00
ci: Add LoongArch64 cross-compile CI for testing
- - - - -
ce6cf240 by Ben Gamari at 2025-05-14T04:25:18-04:00
rts/linker: Don't fail due to RTLD_NOW
In !12264 we started using the NativeObj machinery introduced some time
ago for loading of shared objects. One of the side-effects of this
change is shared objects are now loaded eagerly (i.e. with `RTLD_NOW`).
This is needed by NativeObj to ensure full visibility of the mappings of
the loaded object, which is in turn needed for safe shared object
unloading.
Unfortunately, this change subtly regressed, causing compilation
failures in some programs. Specifically, shared objects which refer to
undefined symbols (e.g. which may be usually provided by either the
executable image or libraries loaded via `dlopen`) will fail to load
with eager binding. This is problematic as GHC loads all package
dependencies while, e.g., evaluating TemplateHaskell splices. This
results in compilation failures in programs depending upon (but not
using at compile-time) packages with undefined symbol references.
To mitigate this NativeObj now first attempts to load an object via
eager binding, reverting to lazy binding (and disabling unloading) on
failure.
See Note [Don't fail due to RTLD_NOW].
Fixes #25943.
- - - - -
88ee8bb5 by Sylvain Henry at 2025-05-14T04:26:15-04:00
Deprecate GHC.JS.Prim.Internal.Build (#23432)
Deprecated as per CLC proposal 329 (https://github.com/haskell/core-libraries-committee/issues/329)
- - - - -
b4ed465b by Cheng Shao at 2025-05-14T04:26:57-04:00
libffi: update to 3.4.8
Bumps libffi submodule.
- - - - -
a3e71296 by Matthew Pickering at 2025-05-14T04:27:38-04:00
Remove leftover trace
- - - - -
2d0ecdc6 by Cheng Shao at 2025-05-14T04:28:19-04:00
Revert "ci: re-enable chrome for wasm ghci browser tests"
This reverts commit fee9b351fa5a35d5778d1252789eacaaf5663ae8.
Unfortunately the chrome test jobs may still timeout on certain
runners (e.g. OpenCape) for unknown reasons.
- - - - -
3b3a5dec by Ben Gamari at 2025-05-15T16:10:01-04:00
Don't emit unprintable characters when printing Uniques
When faced with an unprintable tag we now instead print the codepoint
number.
Fixes #25989.
(cherry picked from commit e832b1fadee66e8d6dd7b019368974756f8f8c46)
- - - - -
e1ef8974 by Mike Pilgrem at 2025-05-16T16:09:14-04:00
Translate iff in Haddock documentation into everyday English
- - - - -
fd64667d by Vladislav Zavialov at 2025-05-20T03:25:08-04:00
Allow the 'data' keyword in import/export lists (#25899)
This patch introduces the 'data' namespace specifier in import and
export lists. The intended use is to import data constructors without
their parent type constructors, e.g.
import Data.Proxy as D (data Proxy)
type DP = D.Proxy -- promoted data constructor
Additionally, it is possible to use 'data' to explicitly qualify any
data constructors or terms, incl. operators and field selectors
import Prelude (Semigroup(data (<>)))
import Data.Function (data (&))
import Data.Monoid (data Dual, data getDual)
x = Dual "Hello" <> Dual "World" & getDual
The implementation mostly builds on top of the existing logic for the
'type' and 'pattern' namespace specifiers, plus there are a few tweaks
to how we generate suggestions in error messages.
- - - - -
acc86753 by Ben Gamari at 2025-05-20T03:25:51-04:00
compiler: Use field selectors when creating BCOs
This makes it easier to grep for these fields.
- - - - -
60a55fd7 by Ben Gamari at 2025-05-20T03:25:51-04:00
compiler: Clarify BCO size
Previously the semantics and size of StgBCO was a bit unclear.
Specifically, the `size` field was documented to contain the size of the
bitmap whereas it was actually the size of the closure *and* bitmap.
Additionally, it was not as clear as it could be that the bitmap was a
full StgLargeBitmap with its own `size` field.
- - - - -
ac9fb269 by Simon Peyton Jones at 2025-05-20T09:19:04-04:00
Track rewriter sets more accurately in constraint solving
This MR addresses #26003, by refactoring the arcane
intricacies of Note [Equalities with incompatible kinds].
NB: now retitled to
Note [Equalities with heterogeneous kinds].
and the main Note for this MR.
In particular:
* Abandon invariant (COERCION-HOLE) in Note [Unification preconditions] in
GHC.Tc.Utils.Unify.
* Abandon invariant (TyEq:CH)) in Note [Canonical equalities] in
GHC.Tc.Types.Constraint.
* Instead: add invariant (REWRITERS) to Note [Unification preconditions]:
unify only if the constraint has an empty rewriter set.
Implementation:
* In canEqCanLHSFinish_try_unification, skip trying unification if there is a
non-empty rewriter set.
* To do this, make sure the rewriter set is zonked; do so in selectNextWorkItem,
which also deals with prioritisation.
* When a coercion hole is filled, kick out inert equalities that have that hole
as a rewriter. It might now be unlocked and available to unify.
* Remove the ad-hoc `ch_hetero_kind` field of `CoercionHole`.
* In `selectNextWorkItem`, priorities equalities withan empty rewriter set.
* Defaulting: see (DE6) in Note [Defaulting equalities]
and Note [Limited defaulting in the ambiguity check]
* Concreteness checks: there is some extra faff to try to get decent
error messages when the FRR (representation-polymorphism) checks
fail. In partiular, add a "When unifying..." explanation when the
representation-polymorphism check arose from another constraint.
- - - - -
86406f48 by Cheng Shao at 2025-05-20T09:19:47-04:00
rts: fix rts_clearMemory logic when sanity checks are enabled
This commit fixes an RTS assertion failure when invoking
rts_clearMemory with +RTS -DS. -DS implies -DZ which asserts that free
blocks contain 0xaa as the designated garbage value. Also adds the
sanity way to rts_clearMemory test to prevent future regression.
Closes #26011.
ChatGPT Codex automatically diagnosed the issue and proposed the
initial patch in a single shot, given a GHC checkout and the following
prompt:
---
Someone is reporting the following error when attempting to use `rts_clearMemory` with the RTS option `-DS`:
```
test.wasm: internal error: ASSERTION FAILED: file rts/sm/Storage.c, line 1216
(GHC version 9.12.2.20250327 for wasm32_unknown_wasi)
Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug
```
What's the culprit? How do I look into this issue?
---
I manually reviewed & revised the patch, tested and submitted it.
- - - - -
7147370b by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: do not allocate strings in bytecode assembler
This patch refactors the compiler to avoid allocating iserv buffers
for BCONPtrStr at assemble-time. Now BCONPtrStr ByteStrings are
recorded as a part of CompiledByteCode, and actual allocation only
happens at link-time. This refactoring is necessary for adding
bytecode serialization functionality, as explained by the revised
comments in this commit.
- - - - -
a67db612 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make bc_strs serializable
This commit makes the bc_strs field in CompiledByteCode serializable;
similar to previous commit, we preserve the ByteString directly and
defer the actual allocation to link-time, as mentioned in updated
comment.
- - - - -
5faf34ef by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make bc_itbls serializable
This commit makes bc_itbls in CompiledByteCode serializable. A
dedicated ConInfoTable datatype has been added in ghci which is the
recipe for dynamically making a datacon's info table, containing the
payload of the MkConInfoTable iserv message.
- - - - -
2abaf8c1 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: remove FFIInfo bookkeeping in BCO
This commit removes the bc_ffis field from CompiledByteCode
completely, as well as all the related bookkeeping logic in
GHC.StgToByteCode. bc_ffis is actually *unused* in the rest of GHC
codebase! It is merely a list of FFIInfo, which is just a remote
pointer of the libffi ffi_cif struct; once we allocate the ffi_cif
struct and put its pointer in a CCALL instruction, we'll never free it
anyway. So there is no point of bookkeeping.
- - - - -
adb9e4d2 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make FFIInfo serializable in BCO
This commit makes all the FFIInfo needed in CCALL instructions
serializable. Previously, when doing STG to BCO lowering, we would
allocate a libffi ffi_cif struct and keep its remote pointer as
FFIInfo; but actually we can just keep the type signature as FFIInfo
and defer the actual allocation to link-time.
- - - - -
200f401b by Cheng Shao at 2025-05-20T17:22:19-04:00
ghci: remove redundant NewBreakModule message
This commit removes the redundant NewBreakModule message from ghci: it
just allocates two strings! This functionality can be implemented with
existing MallocStrings in one iserv call.
- - - - -
ddaadca6 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: make breakpoint module name and unit id serializable
This commit makes breakpoint module name and unit id serializable, in
BRK_FUN instructions as well as ModBreaks. We can simply keep the
module name and unit ids, and defer the buffer allocation to link
time.
- - - - -
a0fde202 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: remove unused newModule
This commit removes the now unused newModule function from GHC.
- - - - -
68c8f140 by Cheng Shao at 2025-05-20T17:22:19-04:00
compiler: add BCONPtrFS for interned top level string literals in BCO
This commit adds BCONPtrFS as a BCO non-pointer literal kind, which
has the same semantics of BCONPtrStr, except it contains a FastString
instead of a ByteString. By using BCONPtrFS to represent top level
string literals that are already FastString in the compilation
pipeline, we enjoy the FastString interning logic and avoid allocating
a bunch of redundant ByteStrings for the same FastStrings, especially
when we lower the BRK_FUN instruction.
- - - - -
f2b532bc by Peng Fan at 2025-05-20T17:23:15-04:00
hadrian: enable GHCi for loongarch64
- - - - -
8ded2330 by kwxm at 2025-05-20T17:24:07-04:00
Fix bugs in `integerRecipMod` and `integerPowMod`
This fixes #26017.
* `integerRecipMod x 1` now returns `(# 1 | #)` for all x; previously it
incorrectly returned `(# | () #)`, indicating failure.
* `integerPowMod 0 e m` now returns `(# | () #)` for e<0 and m>1, indicating
failure; previously it incorrectly returned `(# 0 | #)`.
- - - - -
c9abb87c by Andreas Klebinger at 2025-05-20T17:24:50-04:00
Specialise: Don't float out constraint components.
It was fairly complex to do so and it doesn't seem to improve anything.
Nofib allocations were unaffected as well.
See also Historical Note [Floating dictionaries out of cases]
- - - - -
202b201c by Andreas Klebinger at 2025-05-21T10:16:14-04:00
Interpreter: Add limited support for direct primop evaluation.
This commit adds support for a number of primops directly
to the interpreter. This avoids the indirection of going
through the primop wrapper for those primops speeding interpretation
of optimized code up massively.
Code involving IntSet runs about 25% faster with optimized core and these
changes. For core without breakpoints it's even more pronouced and I
saw reductions in runtime by up to 50%.
Running GHC itself in the interpreter was sped up by ~15% through this
change.
Additionally this comment does a few other related changes:
testsuite:
* Run foundation test in ghci and ghci-opt ways to test these
primops.
* Vastly expand the foundation test to cover all basic primops
by comparing result with the result of calling the wrapper.
Interpreter:
* When pushing arguments for interpreted primops extend each argument to
at least word with when pushing. This avoids some issues with big
endian. We can revisit this if it causes performance issues.
* Restructure the stack chunk check logic. There are now macros for
read accesses which might cross stack chunk boundries and macros which
omit the checks which are used when we statically know we access an
address in the current stack chunk.
- - - - -
67a177b4 by sheaf at 2025-05-21T10:17:04-04:00
QuickLook: do a shape test before unifying
This commit ensures we do a shape test before unifying. This ensures
we don't try to unify a TyVarTv with a non-tyvar, e.g.
alpha[tyv] := Int
On the way, we refactor simpleUnifyCheck:
1. Move the checkTopShape check into simpleUnifyCheck
2. Refactors simpleUnifyCheck to return a value of the new type
SimpleUnifyResult type. Now, simpleUnifyCheck returns "can unify",
"cannot unify" or "dunno" (with "cannot unify" being the new result
it can return). Now:
- touchabilityTest is included; it it fails we return "cannot unify"
- checkTopShape now returns "cannot unify" instead of "dunno" upon failure
3. Move the call to simpleUnifyCheck out of checkTouchableTyVarEq.
After that, checkTouchableTyVarEq becames a simple call to
checkTyEqRhs, so we inline it.
This allows the logic in canEqCanLHSFinish_try_unification to be simplified.
In particular, we now avoid calling 'checkTopShape' twice.
Two further changes suggested by Simon were also implemented:
- In canEqCanLHSFinish, if checkTyEqRhs returns PuFail with
'do_not_prevent_rewriting', we now **continue with this constraint**.
This allows us to use the constraint for rewriting.
- checkTyEqRhs now has a top-level check to avoid flattening a tyfam app
in a top-level equality of the form alpha ~ F tys, as this is
going around in circles. This simplifies the implementation without
any change in behaviour.
Fixes #25950
Fixes #26030
- - - - -
4020972c by sheaf at 2025-05-21T10:17:04-04:00
FixedRuntimeRepError: omit unhelpful explanation
This commit tweaks the FixedRuntimeRepError case of pprTcSolverReportMsg,
to avoid including an explanation which refers to a type variable that
appears nowhere else.
For example, the old error message could look like the following:
The pattern binding does not have a fixed runtime representation.
Its type is:
T :: TYPE R
Cannot unify ‘R’ with the type variable ‘c0’
because the former is not a concrete ‘RuntimeRep’.
With this commit, we now omit the last two lines, because the concrete
type variable (here 'c0') does not appear in the type displayed to the
user (here 'T :: TYPE R').
- - - - -
6d058a69 by Andrea Bedini at 2025-05-21T16:00:51-04:00
Don't fail when ghcversion.h can't be found (#26018)
If ghcversion.h can't be found, don't try to include it. This happens
when there is no rts package in the package db and when -ghcversion-file
argument isn't passed.
Co-authored-by: Syvlain Henry <sylvain(a)haskus.fr>
- - - - -
b1212fbf by Vladislav Zavialov at 2025-05-21T16:01:33-04:00
Implement -Wpattern-namespace-specifier (#25900)
In accordance with GHC Proposal #581 "Namespace-specified imports",
section 2.3 "Deprecate use of pattern in import/export lists", the
`pattern` namespace specifier is now deprecated.
Test cases: T25900 T25900_noext
- - - - -
e650ec3e by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Forward port changelog language from 9.12
- - - - -
94cd9ca4 by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Fix RestructuredText-isms in changelog
- - - - -
7722232c by Ben Gamari at 2025-05-23T03:42:46-04:00
base: Note strictness changes made in 4.16.0.0
Addresses #25886.
- - - - -
3f4b823c by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Factor out ProddableBlocks machinery
- - - - -
6e23fef2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Improve efficiency of proddable blocks structure
Previously the linker's "proddable blocks" check relied on a simple
linked list of spans. This resulted in extremely poor complexity while
linking objects with lots of small sections (e.g. objects built with
split sections).
Rework the mechanism to instead use a simple interval set implemented
via binary search.
Fixes #26009.
- - - - -
ea74860c by Ben Gamari at 2025-05-23T03:43:28-04:00
testsuite: Add simple functional test for ProddableBlockSet
- - - - -
74c4db46 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Drop check for LOAD_LIBRARY_SEARCH_*_DIRS
The `LOAD_LIBRARY_SEARCH_USER_DIRS` and
`LOAD_LIBRARY_SEARCH_DEFAULT_DIRS` were introduced in Windows Vista and
have been available every since. As we no longer support Windows XP we
can drop this check.
Addresses #26009.
- - - - -
972d81d6 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Clean up code style
- - - - -
8a1073a5 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/Hash: Factor out hashBuffer
This is a useful helper which can be used for non-strings as well.
- - - - -
44f509f2 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Fix incorrect use of break in nested for
Previously the happy path of PEi386 used `break` in a double-`for` loop
resulting in redundant calls to `LoadLibraryEx`.
Fixes #26052.
- - - - -
bfb12783 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts: Correctly mark const arguments
- - - - -
08469ff8 by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker/PEi386: Don't repeatedly load DLLs
Previously every DLL-imported symbol would result in a call to
`LoadLibraryEx`. This ended up constituting over 40% of the runtime of
`ghc --interactive -e 42` on Windows. Avoid this by maintaining a
hash-set of loaded DLL names, skipping the call if we have already
loaded the requested DLL.
Addresses #26009.
- - - - -
823d1ccf by Ben Gamari at 2025-05-23T03:43:28-04:00
rts/linker: Expand comment describing ProddableBlockSet
- - - - -
e9de9e0b by Sylvain Henry at 2025-05-23T15:12:34-04:00
Remove emptyModBreaks
Remove emptyModBreaks and track the absence of ModBreaks with `Maybe
ModBreaks`. It avoids testing for null pointers...
- - - - -
17db44c5 by Ben Gamari at 2025-05-23T15:13:16-04:00
base: Expose Backtraces constructor and fields
This was specified in the proposal (CLC #199) yet somehow didn't make it
into the implementation.
Fixes #26049.
- - - - -
b08c08ae by soulomoon at 2025-05-28T01:57:23+08:00
Refactor handling of imported COMPLETE pragmas
from the HPT
Previously, we imported COMPLETE pragmas from all modules in the Home
Package Table (HPT) during type checking. However, since !13675, there
may be non-below modules in the HPT from the dependency tree that we do
not want to import COMPLETE pragmas from. This refactor changes the way
we handle COMPLETE pragmas from the HPT to only import them from modules
that are "below" the current module in the HPT.
- Add hugCompleteSigsBelow to filter COMPLETE pragmas from "below"
modules in the HPT, mirroring hugRulesBelow.
- Move responsibility for calling hugCompleteSigsBelow to tcRnImports,
storing the result in the new tcg_complete_match_env field of TcGblEnv.
- Update getCompleteMatchesTcM to use tcg_complete_match_env.
This refactor only affects how COMPLETE pragmas are imported from the
HPT, imports from external packages are unchanged.
- - - - -
16014bf8 by Hécate Kleidukos at 2025-05-28T20:09:34-04:00
Expose all of Backtraces' internals for ghc-internal
Closes #26049
- - - - -
a0adc30d by Ryan Hendrickson at 2025-05-30T14:12:52-04:00
haddock: Fix links to type operators
- - - - -
7b64697c by Mario Blažević at 2025-05-30T14:13:41-04:00
Introduce parenBreakableList and use it in ppHsContext
- - - - -
5f213bff by fendor at 2025-06-02T09:16:24+02:00
Make GHCi commands compatible with multiple home units
=== Design
We enable all GHCi features that were previously guarded by the `inMulti`
option.
GHCi supported multiple home units up to a certain degree for quite a while now.
The supported feature set was limited, due to a design impasse:
One of the home units must be "active", e.g., there must be one `HomeUnit`
whose `UnitId` is "active" which is returned when calling
```haskell
do
hscActiveUnitId <$> getSession
```
This makes sense in a GHC session, since you are always compiling a particular
Module, but it makes less intuitive sense in an interactive session.
Given an expression to evaluate, we can't easily tell in which "context" the expression
should be parsed, typechecked and evaluated.
That's why initially, most of GHCi features, except for `:reload`ing were disabled
if the GHCi session had more than one `HomeUnitEnv`.
We lift this restriction, enabling all features of GHCi for the multiple home unit case.
To do this, we fundamentally change the `HomeUnitEnv` graph to be multiple home unit first.
Instead of differentiating the case were we have a single home unit and multiple,
we now always set up a multiple home unit session that scales seamlessly to an arbitrary
amount of home units.
We introduce two new `HomeUnitEnv`s that are always added to the `HomeUnitGraph`.
They are:
The "interactive-ghci", called the `interactiveGhciUnit`, contains the same
`DynFlags` that are used by the `InteractiveContext` for interactive evaluation
of expressions.
This `HomeUnitEnv` is only used on the prompt of GHCi, so we may refer to it as
"interactive-prompt" unit.
See Note [Relation between the `InteractiveContext` and `interactiveGhciUnitId`]
for discussing its role.
And the "interactive-session"", called `interactiveSessionUnit` or
`interactiveSessionUnitId`, which is used for loading Scripts into
GHCi that are not `Target`s of any home unit, via `:load` or `:add`.
Both of these "interactive" home units depend on all other `HomeUnitEnv`s that
are passed as arguments on the cli.
Additionally, the "interactive-ghci" unit depends on `interactive-session`.
We always evaluate expressions in the context of the
"interactive-ghci" session.
Since "interactive-ghci" depends on all home units, we can import any `Module`
from the other home units with ease.
As we have a clear `HomeUnitGraph` hierarchy, we can set `interactiveGhciUnitId`
as the active home unit for the full duration of the GHCi session.
In GHCi, we always set `interactiveGhciUnitId` to be the currently active home unit.
=== Implementation Details
Given this design idea, the implementation is relatively straight
forward.
The core insight is that a `ModuleName` is not sufficient to identify a
`Module` in the `HomeUnitGraph`. Thus, large parts of the PR is simply
about refactoring usages of `ModuleName` to prefer `Module`, which has a
`Unit` attached and is unique over the `HomeUnitGraph`.
Consequentially, most usages of `lookupHPT` are likely to be incorrect and have
been replaced by `lookupHugByModule` which is keyed by a `Module`.
In `GHCi/UI.hs`, we make sure there is only one location where we are
actually translating `ModuleName` to a `Module`:
* `lookupQualifiedModuleName`
If a `ModuleName` is ambiguous, we detect this and report it to the
user.
To avoid repeated lookups of `ModuleName`s, we store the `Module` in the
`InteractiveImport`, which additionally simplifies the interface
loading.
A subtle detail is that the `DynFlags` of the `InteractiveContext` are
now stored both in the `HomeUnitGraph` and in the `InteractiveContext`.
In UI.hs, there are multiple code paths where we are careful to update
the `DynFlags` in both locations.
Most importantly in `addToProgramDynFlags`.
---
There is one metric increase in this commit:
-------------------------
Metric Increase:
T4029
-------------------------
It is an increase from 14.4 MB to 16.1 MB (+11.8%) which sounds like a
pretty big regression at first.
However, we argue this increase is solely caused by using more data
structures for managing multiple home units in the GHCi session.
In particular, due to the design decision of using three home units, the
base memory usage increases... but by how much?
A big contributor is the `UnitState`, of which we have three now, which
on its own 260 KB per instance. That makes an additional memory usage of
520 KB, already explaining a third of the overall memory usage increase.
Then we store more elements in the `HomeUnitGraph`, we have more
`HomeUnitEnv` entries, etc...
While we didn't chase down each byte, we looked at the memory usage over time
for both `-hi` and `-hT` profiles and can say with confidence while the memory
usage increased slightly, we did not introduce any space leak, as
the graph looks almost identical as the memory usage graph of GHC HEAD.
---
Adds testcases for GHCi multiple home units session
* Test truly multiple home unit sessions, testing reload logic and code evaluation.
* Test that GHCi commands such as `:all-types`, `:browse`, etc., work
* Object code reloading for home modules
* GHCi debugger multiple home units session
- - - - -
de603d01 by fendor at 2025-06-02T09:16:24+02:00
Update "loading compiled code" GHCi documentation
To use object code in GHCi, the module needs to be compiled for use in
GHCi. To do that, users need to compile their modules with:
* `-dynamic`
* `-this-unit-id interactive-session`
Otherwise, the interface files will not match.
- - - - -
b255a8ca by Vladislav Zavialov at 2025-06-02T16:00:12-04:00
docs: Fix code example for NoListTuplePuns
Without the fix, the example produces an error:
Test.hs:11:3: error: [GHC-45219]
• Data constructor ‘Tuple’ returns type ‘Tuple2 a b’
instead of an instance of its parent type ‘Tuple a’
• In the definition of data constructor ‘Tuple’
In the data type declaration for ‘Tuple’
Fortunately, a one line change makes it compile.
- - - - -
6558467c by Ryan Hendrickson at 2025-06-06T05:46:58-04:00
haddock: Parse math even after ordinary characters
Fixes a bug where math sections were not recognized if preceded by a
character that isn't special (like space or a markup character).
- - - - -
265d0024 by ARATA Mizuki at 2025-06-06T05:47:48-04:00
AArch64 NCG: Fix sub-word arithmetic right shift
As noted in Note [Signed arithmetic on AArch64], we should zero-extend sub-word values.
Fixes #26061
- - - - -
05e9be18 by Simon Hengel at 2025-06-06T05:48:35-04:00
Allow Unicode in "message" and "hints" with -fdiagnostics-as-json
(fixes #26075)
- - - - -
bfa6b70f by ARATA Mizuki at 2025-06-06T05:49:24-04:00
x86 NCG: Fix code generation of bswap64 on i386
Co-authored-by: sheaf <sam.derbyshire(a)gmail.com>
Fix #25601
- - - - -
35826d8b by Matthew Pickering at 2025-06-08T22:00:41+01:00
Hadrian: Add option to generate .hie files for stage1 libraries
The +hie_files flavour transformer can be enabled to produce hie files
for stage1 libraries. The hie files are produced in the
"extra-compilation-artifacts" folder and copied into the resulting
bindist.
At the moment the hie files are not produced for the release flavour,
they add about 170M to the final bindist.
Towards #16901
- - - - -
e2467dbd by Ryan Hendrickson at 2025-06-09T13:07:05-04:00
Fix various failures to -fprint-unicode-syntax
- - - - -
1d99d3e4 by maralorn at 2025-06-12T03:47:39-04:00
Add necessary flag for js linking
- - - - -
974d5734 by maralorn at 2025-06-12T03:47:39-04:00
Don’t use additional linker flags to detect presence of -fno-pie in configure.ac
This mirrors the behavior of ghc-toolchain
- - - - -
1e9eb118 by Andrew Lelechenko at 2025-06-12T03:48:21-04:00
Add HasCallStack to Control.Monad.Fail.fail
CLC proposal https://github.com/haskell/core-libraries-committee/issues/327
2% compile-time allocations increase in T3064, likely because `fail`
is now marginally more expensive to compile.
Metric Increase:
T3064
- - - - -
6d12060f by meooow25 at 2025-06-12T14:26:07-04:00
Bump containers submodule to 0.8
Also
* Disable -Wunused-imports for containers
* Allow containers-0.8 for in-tree packages
* Bump some submodules so that they allow containers-0.8. These are not
at any particular versions.
* Remove unused deps containers and split from ucd2haskell
* Fix tests affected by the new containers and hpc-bin
- - - - -
537bd233 by Peng Fan at 2025-06-12T14:27:02-04:00
NCG/LA64: Optimize code generation and reduce build-directory size.
1. makeFarBranches: Prioritize fewer instruction sequences.
2. Prefer instructions with immediate numbers to reduce register moves,
e.g. andi,ori,xori,addi.
3. Ppr: Remove unnecessary judgments.
4. genJump: Avoid "ld+jr" as much as possible.
5. BCOND and BCOND1: Implement conditional jumps with two jump ranges,
with limited choice of the shortest.
6. Implement FSQRT, CLT, CTZ.
7. Remove unnecessary code.
- - - - -
19f20861 by Simon Peyton Jones at 2025-06-13T09:51:11-04:00
Improve redundant constraints for instance decls
Addresses #25992, which showed that the default methods
of an instance decl could make GHC fail to report redundant
constraints.
Figuring out how to do this led me to refactor the computation
of redundant constraints. See the entirely rewritten
Note [Tracking redundant constraints]
in GHC.Tc.Solver.Solve
- - - - -
1d02798e by Matthew Pickering at 2025-06-13T09:51:54-04:00
Refactor the treatment of nested Template Haskell splices
* The difference between a normal splice, a quasiquoter and implicit
splice caused by lifting is stored in the AST after renaming.
* Information that the renamer learns about splices is stored in the
relevant splice extension points (XUntypedSpliceExpr, XQuasiQuote).
* Normal splices and quasi quotes record the flavour of splice
(exp/pat/dec etc)
* Implicit lifting stores information about why the lift was attempted,
so if it fails, that can be reported to the user.
* After renaming, the decision taken to attempt to implicitly lift a
variable is stored in the `XXUntypedSplice` extension field in the
`HsImplicitLiftSplice` constructor.
* Since all the information is stored in the AST, in `HsUntypedSplice`,
the type of `PendingRnSplice` now just stores a `HsUntypedSplice`.
* Error messages since the original program can be easily
printed, this is noticeable in the case of implicit lifting.
* The user-written syntax is directly type-checked. Before, some
desugaring took place in the
* Fixes .hie files to work better with nested splices (nested splices
are not indexed)
* The location of the quoter in a quasiquote is now located, so error
messages will precisely point to it (and again, it is indexed by hie
files)
In the future, the typechecked AST should also retain information about
the splices and the specific desugaring being left to the desugarer.
Also, `runRnSplice` should call `tcUntypedSplice`, otherwise the
typechecking logic is duplicated (see the `QQError` and `QQTopError`
tests for a difference caused by this).
- - - - -
f93798ba by Cheng Shao at 2025-06-13T09:52:35-04:00
libffi: update to 3.5.1
Bumps libffi submodule.
- - - - -
c7aa0c10 by Andreas Klebinger at 2025-06-15T05:47:24-04:00
Revert "Specialise: Don't float out constraint components."
This reverts commit c9abb87ccc0c91cd94f42b3e36270158398326ef.
Turns out two benchmarks from #19747 regresses by a factor of 7-8x if
we do not float those out.
- - - - -
fd998679 by Krzysztof Gogolewski at 2025-06-15T05:48:06-04:00
Fix EPT enforcement when mixing unboxed tuples and non-tuples
The code was assuming that an alternative cannot be returning a normal
datacon and an unboxed tuple at the same time. However, as seen in #26107,
this can happen when using a GADT to refine the representation type.
The solution is just to conservatively return TagDunno.
- - - - -
e64b3f16 by ARATA Mizuki at 2025-06-17T10:13:42+09:00
MachRegs.h: Don't define NO_ARG_REGS when a XMM register is defined
On i386, MAX_REAL_VANILLA_REG is 1, but MAX_REAL_XMM_REG is 4.
If we define NO_ARG_REGS on i386, programs that use SIMD vectors may segfault.
Closes #25985
A couple of notes on the BROKEN_TESTS field:
* This fixes the segfault from T25062_V16.
* The failure from T22187_run was fixed in an earlier commit (see #25561),
but BROKEN_TESTS was missed at that time. Now should be a good time to
mark it fixed.
- - - - -
3e7c6b4d by Matthew Pickering at 2025-06-18T15:34:04-04:00
Improve error messages when implicit lifting fails
This patch concerns programs which automatically try to fix level errors
by inserting `Lift`. For example:
```
foo x = [| x |]
~>
foo x = [| $(lift x) |]
```
Before, there were two problems with the message.
1. (#26031), the location of the error was reported as the whole
quotation.
2. (#26035), the message just mentions there is no Lift instance, but
gives no indicate why the user program needed a Lift instance in the
first place.
This problem is especially bad when you disable
`ImplicitStagePersistence`, so you just end up with a confusing "No
instance for" message rather than an error message about levels
This patch fixes both these issues.
Firstly, `PendingRnSplice` differentiates between a user-written splice
and an implicit lift. Then, the Lift instance is precisely requested
with a specific origin in the typechecker. If the instance fails to be
solved, the message is reported using the `TcRnBadlyLevelled`
constructor (like a normal level error).
Fixes #26031, #26035
- - - - -
44b8cee2 by Cheng Shao at 2025-06-18T15:34:46-04:00
testsuite: add T26120 marked as broken
- - - - -
894a04f3 by Cheng Shao at 2025-06-18T15:34:46-04:00
compiler: fix GHC.SysTools.Ar archive member size writing logic
This patch fixes a long-standing bug in `GHC.SysTools.Ar` that emits
the wrong archive member size in each archive header. It should encode
the exact length of the member payload, excluding any padding byte,
otherwise malformed archive that extracts a broken object with an
extra trailing byte could be created.
Apart from the in-tree `T26120` test, I've also created an out-of-tree
testsuite at https://github.com/TerrorJack/ghc-ar-quickcheck that
contains QuickCheck roundtrip tests for `GHC.SysTools.Ar`. With this
fix, simple roundtrip tests and `writeGNUAr`/GNU `ar` roundtrip test
passes. There might be more bugs lurking in here, but this patch is
still a critical bugfix already.
Fixes #26120 #22586.
Co-authored-by: Codex <codex(a)openai.com>
- - - - -
f677ab5f by Lauren Yim at 2025-06-18T15:35:37-04:00
fix some typos in the warnings page in the user guide
- - - - -
b968e1c1 by Rodrigo Mesquita at 2025-06-18T15:36:18-04:00
Add a frozen callstack to throwGhcException
Fixes #25956
- - - - -
a5e0c3a3 by fendor at 2025-06-18T15:36:59-04:00
Update using.rst to advertise full mhu support for GHCi
- - - - -
d3e60e97 by Ryan Scott at 2025-06-18T22:29:21-04:00
Deprecate -Wdata-kinds-tc, make DataKinds issues in typechecker become errors
!11314 introduced the `-Wdata-kinds-tc` warning as part of a fix for #22141.
This was a temporary stopgap measure to allow users who were accidentally
relying on code which needed the `DataKinds` extension in order to typecheck
without having to explicitly enable the extension.
Now that some amount of time has passed, this patch deprecates
`-Wdata-kinds-tc` and upgrades any `DataKinds`-related issues in the
typechecker (which were previously warnings) into errors.
- - - - -
fd5b5177 by Ryan Hendrickson at 2025-06-18T22:30:06-04:00
haddock: Add redact-type-synonyms pragma
`{-# OPTIONS_HADDOCK redact-type-synonyms #-}` pragma will hide the RHS
of type synonyms, and display the result kind instead, if the RHS
contains any unexported types.
- - - - -
fbc0b92a by Vladislav Zavialov at 2025-06-22T04:25:16+03:00
Visible forall in GADTs (#25127)
Add support for visible dependent quantification `forall a -> t` in
types of data constructors, e.g.
data KindVal a where
K :: forall k.
forall (a::k) -> -- now allowed!
k ->
KindVal a
For details, see docs/users_guide/exts/required_type_arguments.rst,
which has gained a new subsection.
DataCon in compiler/GHC/Core/DataCon.hs
---------------------------------------
The main change in this patch is that DataCon, the Core representation
of a data constructor, now uses a different type to store user-written
type variable binders:
- dcUserTyVarBinders :: [InvisTVBinder]
+ dcUserTyVarBinders :: [TyVarBinder]
where
type TyVarBinder = VarBndr TyVar ForAllTyFlag
type InvisTVBinder = VarBndr TyVar Specificity
and
data Specificity = InferredSpec | SpecifiedSpec
data ForAllTyFlag = Invisible Specificity | Required
This change necessitates some boring, mechanical changes scattered
throughout the diff:
... is now used in place of ...
-----------------+---------------
TyVarBinder | InvisTVBinder
IfaceForAllBndr | IfaceForAllSpecBndr
Specified | SpecifiedSpec
Inferred | InferredSpec
mkForAllTys | mkInvisForAllTys
additionally,
tyVarSpecToBinders -- added or removed calls
ifaceForAllSpecToBndrs -- removed calls
Visibility casts in mkDataConRep
--------------------------------
Type abstractions in Core (/\a. e) always have type (forall a. t)
because coreTyLamForAllTyFlag = Specified. This is also true of data
constructor workers. So we may be faced with the following:
data con worker: (forall a. blah)
data con wrapper: (forall a -> blah)
In this case the wrapper must use a visibility cast (e |> ForAllCo ...)
with appropriately set fco_vis{L,R}. Relevant functions:
mkDataConRep in compiler/GHC/Types/Id/Make.hs
dataConUserTyVarBindersNeedWrapper in compiler/GHC/Core/DataCon.hs
mkForAllVisCos in compiler/GHC/Core/Coercion.hs
mkCoreTyLams in compiler/GHC/Core/Make.hs
mkWpForAllCast in compiler/GHC/Tc/Types/Evidence.hs
More specifically:
- dataConUserTyVarBindersNeedWrapper has been updated to answer "yes"
if there are visible foralls in the type of the data constructor.
- mkDataConRep now uses mkCoreTyLams to generate the big lambda
abstractions (/\a b c. e) in the data con wrapper.
- mkCoreTyLams is a variant of mkCoreLams that applies visibility casts
as needed. It similar in purpose to the pre-existing mkWpForAllCast,
so the common bits have been factored out into mkForAllVisCos.
ConDecl in compiler/Language/Haskell/Syntax/Decls.hs
----------------------------------------------------
The surface syntax representation of a data constructor declaration is
ConDecl. In accordance with the proposal, only GADT syntax is extended
with support for visible forall, so we are interested in ConDeclGADT.
ConDeclGADT's field con_bndrs has been renamed to con_outer_bndrs
and is now accompanied by con_inner_bndrs:
con_outer_bndrs :: XRec pass (HsOuterSigTyVarBndrs pass)
con_inner_bndrs :: [HsForAllTelescope pass]
Visible foralls always end up in con_inner_bndrs. The outer binders are
stored and processed separately to support implicit quantification and
the forall-or-nothing rule, a design established by HsSigType.
A side effect of this change is that even in absence of visible foralls,
GHC now permits multiple invisible foralls, e.g.
data T a where { MkT :: forall a b. forall c d. ... -> T a }
But of course, this is done in service of making at least some of these
foralls visible. The entire compiler front-end has been updated to deal
with con_inner_bndrs. See the following modified or added functions:
Parser:
mkGadtDecl in compiler/GHC/Parser/PostProcess.hs
splitLHsGadtTy in compiler/GHC/Hs/Type.hs
Pretty-printer:
pprConDecl in compiler/GHC/Hs/Decls.hs
pprHsForAllTelescope in compiler/GHC/Hs/Type.hs
Renamer:
rnConDecl in compiler/GHC/Rename/Module.hs
bindHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
extractHsForAllTelescopes in compiler/GHC/Rename/HsType.hs
Type checker:
tcConDecl in compiler/GHC/Tc/TyCl.hs
tcGadtConTyVarBndrs in compiler/GHC/Tc/Gen/HsType.hs
Template Haskell
----------------
The TH AST is left unchanged for the moment to avoid breakage. An
attempt to quote or reify a data constructor declaration with visible
forall in its type will result an error:
data ThRejectionReason -- in GHC/HsToCore/Errors/Types.hs
= ...
| ThDataConVisibleForall -- new error constructor
However, as noted in the previous section, GHC now permits multiple
invisible foralls, and TH was updated accordingly. Updated code:
repC in compiler/GHC/HsToCore/Quote.hs
reifyDataCon in compiler/GHC/Tc/Gen/Splice.hs
ppr @Con in libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
Pattern matching
----------------
Everything described above concerns data constructor declarations, but
what about their use sites? Now it is trickier to type check a pattern
match fn(Con a b c)=... because we can no longer assume that a,b,c are
all value arguments. Indeed, some or all of them may very well turn out
to be required type arguments.
To that end, see the changes to:
tcDataConPat in compiler/GHC/Tc/Gen/Pat.hs
splitConTyArgs in compiler/GHC/Tc/Gen/Pat.hs
and the new helpers split_con_ty_args, zip_pats_bndrs.
This is also the reason the TcRnTooManyTyArgsInConPattern error
constructor has been removed. The new code emits TcRnArityMismatch
or TcRnIllegalInvisibleTypePattern.
Summary
-------
DataCon, ConDecl, as well as all related functions have been updated to
support required type arguments in data constructors.
Test cases:
HieGadtConSigs GadtConSigs_th_dump1 GadtConSigs_th_pprint1
T25127_data T25127_data_inst T25127_infix
T25127_newtype T25127_fail_th_quote T25127_fail_arity
TyAppPat_Tricky
Co-authored-by: mniip <mniip(a)mniip.com>
- - - - -
ae003a3a by Teo Camarasu at 2025-06-23T05:21:48-04:00
linters: lint-whitespace: bump upper-bound for containers
The version of containers was bumped in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/13989
- - - - -
0fb37893 by Matthew Pickering at 2025-06-23T13:55:10-04:00
Move ModuleGraph into UnitEnv
The ModuleGraph is a piece of information associated with the
ExternalPackageState and HomeUnitGraph. Therefore we should store it
inside the HomeUnitEnv.
- - - - -
3bf6720e by soulomoon at 2025-06-23T13:55:52-04:00
Remove hptAllFamInstances usage during upsweep
Fixes #26118
This change eliminates the use of hptAllFamInstances during the upsweep phase,
as it could access non-below modules from the home package table.
The following updates were made:
* Updated checkFamInstConsistency to accept an explicit ModuleEnv FamInstEnv
parameter and removed the call to hptAllFamInstances.
* Adjusted hugInstancesBelow so we can construct ModuleEnv FamInstEnv
from its result,
* hptAllFamInstances and allFamInstances functions are removed.
- - - - -
83ee7b78 by Ben Gamari at 2025-06-24T05:02:07-04:00
configure: Don't force value of OTOOL, etc. if not present
Previously if `otool` and `install_name_tool` were not present they
would be overridden by `fp_settings.m4`. This logic was introduced in
4ff93292243888545da452ea4d4c1987f2343591 without explanation.
- - - - -
9329c9e1 by Ben Gamari at 2025-06-24T05:02:07-04:00
ghc-toolchain: Add support for otool, install_name_tool
Fixes part of ghc#23675.
- - - - -
25f5c998 by Ben Gamari at 2025-06-24T05:02:08-04:00
ghc-toolchain: Add support for llc, opt, llvm-as
Fixes #23675.
- - - - -
51d150dd by Rodrigo Mesquita at 2025-06-24T05:02:08-04:00
hadrian: Use settings-use-distro-mingw directly
The type `ToolchainSetting` only made sense when we had more settings to
fetch from the system config file. Even then "settings-use-distro-mingw"
is arguably not a toolchain setting.
With the fix for #23675, all toolchain tools were moved to the
`ghc-toolchain` `Toolchain` format. Therefore, we can inline
`settings-use-distro-mingw` accesses and delete `ToolchainSetting`.
- - - - -
dcf68a83 by Rodrigo Mesquita at 2025-06-24T05:02:08-04:00
configure: Check LlvmTarget exists for LlvmAsFlags
If LlvmTarget was empty, LlvmAsFlags would be just "--target=".
If it is empty now, simply keep LlvmAsFlags empty.
ghc-toolchain already does this right. This fix makes the two
configurations match up.
- - - - -
580a3353 by Ben Gamari at 2025-06-24T05:02:51-04:00
rts/linker/LoadArchive: Use bool
Improve type precision by using `bool` instead of `int` and `StgBool`.
- - - - -
76d1041d by Ben Gamari at 2025-06-24T05:02:51-04:00
rts/linker/LoadArchive: Don't rely on file extensions for identification
Previously archive members would be identified via their file extension,
as described in #13103. We now instead use a more principled approach,
relying on the magic number in the member's header.
As well, we refactor treatment of archive format detection to improve
code clarity and error handling.
Closes #13103.
- - - - -
4b748a99 by Teo Camarasu at 2025-06-24T15:31:07-04:00
template-haskell: improve changelog
stable -> more stable, just to clarify that this interface isn't fully stable.
errornously -> mistakenly: I typod this and also let's go for a simpler word
- - - - -
e358e477 by Sylvain Henry at 2025-06-24T15:31:58-04:00
Bump stack resolver to use GHC 9.6.7
Cf #26139
- - - - -
4bf5eb63 by fendor at 2025-06-25T17:05:43-04:00
Teach `:reload` about multiple home units
`:reload` needs to lookup the `ModuleName` and must not assume the given
`ModuleName` is in the current `HomeUnit`.
We add a new utility function which allows us to find a `HomeUnitModule`
instead of a `Module`.
Further, we introduce the `GhciCommandError` type which can be used to
abort the execution of a GHCi command.
This error is caught and printed in a human readable fashion.
- - - - -
b3d97bb3 by fendor at 2025-06-25T17:06:25-04:00
Implement `-fno-load-initial-targets` flag
We add the new flag `-fno-load-initial-targets` which doesn't load all `Target`s
immediately but only computes the module graph for all `Target`s.
The user can then decide to load modules from that module graph using
the syntax:
ghci> :reload <Mod>
This will load everything in the module graph up to `Mod`.
The user can return to the initial state by using the builtin target
`none` to unload all modules.
ghci> :reload none
Is in principle identical to starting a new session with the
`-fno-load-initial-targets` flag.
The `-fno-load-initial-targets` flag allows for faster startup time of GHCi when a
user has lots of `Target`s.
We additionally extend the `:reload` command to accept multiple
`ModuleName`s. For example:
ghci> :reload <Mod1> <Mod2>
Loads all modules up to the modules `Mod1` and `Mod2`.
- - - - -
49f44e52 by Teo Camarasu at 2025-06-26T04:19:51-04:00
Expose ghc-internal unit id through the settings file
This in combination with the unit id of the compiler library allows
cabal to know of the two unit ids that should not be reinstalled (in
specific circumstances) as:
- when using plugins, we want to link against exactly the compiler unit
id
- when using TemplateHaskell we want to link against exactly the package
that contains the TemplateHaskell interfaces, which is `ghc-internal`
See: <https://github.com/haskell/cabal/issues/10087>
Resolves #25282
- - - - -
499c4efe by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Fix and clean up capture of timings
* Fixes the typo that caused 'cat ci-timings' to report "no such file or
directory"
* Gave ci_timings.txt a file extension so it may play better with other
systems
* Fixed the use of time_it so all times are recorded
* Fixed time_it to print name along with timing
- - - - -
86c90c9e by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Update collapsible section usage
The syntax apparently changed at some point.
- - - - -
04308ee4 by Bryan Richter at 2025-06-26T04:20:33-04:00
CI: Add more collapsible sections
- - - - -
43b606bb by Florian Ragwitz at 2025-06-27T16:31:26-04:00
Tick uses of wildcard/pun field binds as if using the record selector function
Fixes #17834.
See Note [Record-selector ticks] for additional reasoning behind this as well
as an overview of the implementation details and future improvements.
- - - - -
d4952549 by Ben Gamari at 2025-06-27T16:32:08-04:00
testsuite/caller-cc: Make CallerCc[123] less sensitive
These were previously sensitive to irrelevant changes in program
structure. To avoid this we filter out all by lines emitted by the
-fcaller-cc from the profile.
- - - - -
8d33d048 by Berk Özkütük at 2025-07-07T20:42:20-04:00
Consider `PromotedDataCon` in `tyConStupidTheta`
Haddock checks data declarations for the stupid theta so as not to
pretty-print them as empty contexts. Type data declarations end up as
`PromotedDataCon`s by the time Haddock performs this check, causing a
panic. This commit extends `tyConStupidTheta` so that it returns an
empty list for `PromotedDataCon`s. This decision was guided by the fact
that type data declarations never have data type contexts (see (R1) in
Note [Type data declarations]).
Fixes #25739.
- - - - -
a26243fd by Ryan Hendrickson at 2025-07-07T20:43:07-04:00
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
- - - - -
0fb24420 by Rodrigo Mesquita at 2025-07-07T20:43:49-04:00
hadrian: Fallback logic for internal interpreter
When determining whether to build the internal interpreter, the `make`
build system had a fallback case for platforms not in the list of
explicitly-supported operating systems and architectures.
This fallback says we should try to build the internal interpreter if
building dynamic GHC programs (if the architecture is unknown).
Fixes #24098
- - - - -
fe925bd4 by Ben Gamari at 2025-07-07T20:44:30-04:00
users-guide: Reference Wasm FFI section
- - - - -
5856284b by Ben Gamari at 2025-07-07T20:44:30-04:00
users-guide: Fix too-short heading warning
- - - - -
a48dcdf3 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Reorganise documentation for allocate* functions
Consolodate interface information into the .h file, keeping just
implementation details in the .c file.
Use Notes stlye in the .h file and refer to notes from the .c file.
- - - - -
de5b528c by Duncan Coutts at 2025-07-07T20:45:18-04:00
Introduce common utilities for allocating arrays
The intention is to share code among the several places that do this
already.
- - - - -
b321319d by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Heap.c
The CMM primop can now report heap overflow.
- - - - -
1d557ffb by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in ThreadLabels.c
Replacing a local utility.
- - - - -
e59a1430 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Threads.c
Replacing local open coded version.
- - - - -
482df1c9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Add exitHeapOverflow helper utility
This will be useful with the array alloc functions, since unlike
allocate/allocateMaybeFail, they do not come in two versions. So if it's
not convenient to propagate failure, then one can use this.
- - - - -
4d3ec8f9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Weak.c
Also add a cpp macro CCS_SYSTEM_OR_NULL which does what it says. The
benefit of this is that it allows us to referece CCS_SYSTEM even when
we're not in PROFILING mode. That makes abstracting over profiling vs
normal mode a lot easier.
- - - - -
0c4f2fde by Duncan Coutts at 2025-07-07T20:45:18-04:00
Convert the array alloc primops to use the new array alloc utils
- - - - -
a3354ad9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
While we're at it, add one missing 'likely' hint
To a cmm primops that raises an exception, like the others now do.
- - - - -
33b546bd by meooow25 at 2025-07-07T20:46:09-04:00
Keep scanl' strict in the head on rewrite
`scanl'` forces elements to WHNF when the corresponding `(:)`s are
forced. The rewrite rule for `scanl'` missed forcing the first element,
which is fixed here with a `seq`.
- - - - -
8a69196e by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger/rts: Allow toggling step-in per thread
The RTS global flag `rts_stop_next_breakpoint` globally sets the
interpreter to stop at the immediate next breakpoint.
With this commit, single step mode can additionally be set per thread in
the TSO flag (TSO_STOP_NEXT_BREAKPOINT).
Being able to toggle "stop at next breakpoint" per thread is an
important requirement for implementing "stepping out" of a function in a
multi-threaded context.
And, more generally, having a per-thread flag for single-stepping paves the
way for multi-threaded debugging.
That said, when we want to enable "single step" mode for the whole
interpreted program we still want to stop at the immediate next
breakpoint, whichever thread it belongs to.
That's why we also keep the global `rts_stop_next_breakpoint` flag, with
`rts_enableStopNextBreakpointAll` and `rts_disableStopNextBreakpointAll` helpers.
Preparation for #26042
- - - - -
73d3f864 by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
docs: Case continuation BCOs
This commit documents a subtle interaction between frames for case BCOs
and their parents frames. Namely, case continuation BCOs may refer to
(non-local) variables that are part of the parent's frame.
The note expanding a bit on these details is called [Case continuation BCOs]
- - - - -
d7aeddcf by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger: Implement step-out feature
Implements support for stepping-out of a function (aka breaking right after
returning from a function) in the interactive debugger.
It also introduces a GHCi command :stepout to step-out of a function
being debugged in the interpreter. The feature is described as:
Stop at the first breakpoint immediately after returning from the current
function scope.
Known limitations: because a function tail-call does not push a stack
frame, if step-out is used inside of a function that was tail-called,
execution will not be returned to its caller, but rather its caller's
first non-tail caller. On the other hand, it means the debugger
follows the more realistic execution of the program.
In the following example:
.. code-block:: none
f = do
a
b <--- (1) set breakpoint then step in here
c
b = do
...
d <--- (2) step-into this tail call
d = do
...
something <--- (3) step-out here
...
Stepping-out will stop execution at the `c` invokation in `f`, rather than
stopping at `b`.
The key idea is simple: When step-out is enabled, traverse the runtime
stack until a continuation BCO is found -- and enable the breakpoint
heading that BCO explicitly using its tick-index.
The details are specified in `Note [Debugger: Step-out]` in `rts/Interpreter.c`.
Since PUSH_ALTS BCOs (representing case continuations) were never headed
by a breakpoint (unlike the case alternatives they push), we introduced
the BRK_ALTS instruction to allow the debugger to set a case
continuation to stop at the breakpoint heading the alternative that is
taken. This is further described in `Note [Debugger: BRK_ALTS]`.
Fixes #26042
- - - - -
5d9adf51 by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger: Filter step-out stops by SrcSpan
To implement step-out, the RTS looks for the first continuation frame on
the stack and explicitly enables its entry breakpoint. However, some
continuations will be contained in the function from which step-out was
initiated (trivial example is a case expression).
Similarly to steplocal, we will filter the breakpoints at which the RTS
yields to the debugger based on the SrcSpan. When doing step-out, only
stop if the breakpoint is /not/ contained in the function from which we
initiated it.
This is especially relevant in monadic statements such as IO which is
compiled to a long chain of case expressions.
See Note [Debugger: Filtering step-out stops]
- - - - -
7677adcc by Cheng Shao at 2025-07-08T07:40:29-04:00
compiler: make ModBreaks serializable
- - - - -
14f67c6d by Rodrigo Mesquita at 2025-07-08T07:40:29-04:00
refactor: "Inspecting the session" moved from GHC
Moved utilities for inspecting the session from the GHC module to
GHC.Driver.Session.Inspect
Purely a clean up
- - - - -
9d3f484a by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Pass the HUG to readModBreaks, not HscEnv
A minor cleanup. The associated history and setupBreakpoint functions
are changed accordingly.
- - - - -
b595f713 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Move readModBreaks to GHC.Runtime.Interpreter
With some small docs changes
- - - - -
d223227a by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Move interpreterProfiled to Interp.Types
Moves interpreterProfiled and interpreterDynamic to
GHC.Runtime.Interpreter.Types from GHC.Runtime.Interpreter.
- - - - -
7fdd0a3d by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Don't import GHC in Debugger.Breakpoints
Remove the top-level
import GHC
from GHC.Runtime.Debugger.Breakpoints
This makes the module dependencies more granular and cleans up the
qualified imports from the code.
- - - - -
5e4da31b by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
refactor: Use BreakpointId in Core and Ifaces
- - - - -
741ac3a8 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
stg2bc: Derive BcM via ReaderT StateT
A small refactor that simplifies GHC.StgToByteCode by deriving-via the
Monad instances for BcM. This is done along the lines of previous
similar refactors like 72b54c0760bbf85be1f73c1a364d4701e5720465.
- - - - -
0414fcc9 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
refact: Split InternalModBreaks out of ModBreaks
There are currently two competing ways of referring to a Breakpoint:
1. Using the Tick module + Tick index
2. Using the Info module + Info index
1. The Tick index is allocated during desugaring in `mkModBreaks`. It is
used to refer to a breakpoint associated to a Core Tick. For a given
Tick module, there are N Ticks indexed by Tick index.
2. The Info index is allocated during code generation (in StgToByteCode)
and uniquely identifies the breakpoints at runtime (and is indeed used
to determine which breakpoint was hit at runtime).
Why we need both is described by Note [Breakpoint identifiers].
For every info index we used to keep a `CgBreakInfo`, a datatype containing
information relevant to ByteCode Generation, in `ModBreaks`.
This commit splits out the `IntMap CgBreakInfo` out of `ModBreaks` into
a new datatype `InternalModBreaks`.
- The purpose is to separate the `ModBreaks` datatype, which stores
data associated from tick-level information which is fixed after
desugaring, from the unrelated `IntMap CgBreakInfo` information
accumulated during bytecode generation.
- We move `ModBreaks` to GHC.HsToCore.Breakpoints
The new `InternalModBreaks` simply combines the `IntMap CgBreakInfo`
with `ModBreaks`. After code generation we construct an
`InternalModBreaks` with the `CgBreakInfo`s we accumulated and the
existing `ModBreaks` and store that in the compiled BCO in `bc_breaks`.
- Note that we previously only updated the `modBreaks_breakInfo`
field of `ModBreaks` at this exact location, and then stored the
updated `ModBreaks` in the same `bc_breaks`.
- We put this new datatype in GHC.ByteCode.Breakpoints
The rest of the pipeline for which CgBreakInfo is relevant is
accordingly updated to also use `InternalModBreaks`
- - - - -
2a097955 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Use BreakpointIds in bytecode gen
Small clean up to use BreakpointId and InternalBreakpointId more
uniformly in bytecode generation rather than using Module + Ix pairs
- - - - -
0515cc2f by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
ghci: Allocate BreakArrays at link time only
Previously, a BreakArray would be allocated with a slot for every tick
in a module at `mkModBreaks`, in HsToCore. However, this approach has
a few downsides:
- It interleaves interpreter behaviour (allocating arrays for
breakpoints) within the desugarer
- It is inflexible in the sense it is impossible for the bytecode
generator to add "internal" breakpoints that can be triggered at
runtime, because those wouldn't have a source tick. (This is relevant
for our intended implementation plan of step-out in #26042)
- It ties the BreakArray indices to the *tick* indexes, while at runtime
we would rather just have the *info* indexes (currently we have both
because BreakArrays are indexed by the *tick* one).
Paving the way for #26042 and #26064, this commit moves the allocation
of BreakArrays to bytecode-loading time -- akin to what is done for CCS
arrays.
Since a BreakArray is allocated only when bytecode is linked, if a
breakpoint is set (e.g. `:break 10`) before the bytecode is linked,
there will exist no BreakArray to trigger the breakpoint in.
Therefore, the function to allocate break arrays (`allocateBreakArrays`)
is exposed and also used in GHC.Runtime.Eval to allocate a break array
when a breakpoint is set, if it doesn't exist yet (in the linker env).
- - - - -
8016561f by Simon Peyton Jones at 2025-07-08T07:41:13-04:00
Add a test for T26176
- - - - -
454cd682 by Simon Peyton Jones at 2025-07-08T07:41:13-04:00
Add test for #14010
This test started to work in GHC 9.6 and has worked since.
This MR just adds a regression test
- - - - -
ea2c6673 by Teo Camarasu at 2025-07-08T13:24:43-04:00
Implement user-defined allocation limit handlers
Allocation Limits allow killing a thread if they allocate more than a
user-specified limit.
We extend this feature to allow more versatile behaviour.
- We allow not killing the thread if the limit is exceeded.
- We allow setting a custom handler to be called when the limit is exceeded.
User-specified allocation limit handlers run in a fresh thread and are passed
the ThreadId of the thread that exceeded its limit.
We introduce utility functions for getting and setting the allocation
limits of other threads, so that users can reset the limit of a thread
from a handler. Both of these are somewhat coarse-grained as we are
unaware of the allocations in the current nursery chunk.
We provide several examples of usages in testsuite/tests/rts/T22859.hs
Resolves #22859
- - - - -
03e047f9 by Simon Hengel at 2025-07-08T13:25:25-04:00
Fix typo in using.rst
- - - - -
67957854 by Ben Gamari at 2025-07-09T09:44:44-04:00
compiler: Import AnnotationWrapper from ghc-internal
Since `GHC.Desugar` exported from `base` has been deprecated.
- - - - -
813d99d6 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-compact: Eliminate dependency on ghc-prim
- - - - -
0ec952a1 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Eliminate dependency on ghc-prim
- - - - -
480074c3 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Drop redundant import
- - - - -
03455829 by Ben Gamari at 2025-07-09T09:44:45-04:00
ghc-prim: Bump version to 0.13.1
There are no interface changes from 0.13.0 but the implementation now
lives in `ghc-internal`.
- - - - -
d315345a by Ben Gamari at 2025-07-09T09:44:45-04:00
template-haskell: Bump version number to 2.24.0.0
Bumps exceptions submodule.
- - - - -
004c800e by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump GHC version number to 9.14
- - - - -
eb1a3816 by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump parsec to 3.1.18.0
Bumps parsec submodule.
- - - - -
86f83296 by Ben Gamari at 2025-07-09T09:44:45-04:00
unix: Bump to 2.8.7.0
Bumps unix submodule.
- - - - -
89e13998 by Ben Gamari at 2025-07-09T09:44:45-04:00
binary: Bump to 0.8.9.3
Bumps binary submodule.
- - - - -
55fff191 by Ben Gamari at 2025-07-09T09:44:45-04:00
Win32: Bump to 2.14.2.0
Bumps Win32 submodule.
- - - - -
7dafa40c by Ben Gamari at 2025-07-09T09:44:45-04:00
base: Bump version to 4.22.0
Bumps various submodules.
- - - - -
ef03d8b8 by Rodrigo Mesquita at 2025-07-09T09:45:28-04:00
base: Export displayExceptionWithInfo
This function should be exposed from base following CLC#285
Approved change in CLC#344
Fixes #26058
- - - - -
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
f2357b3b by Sebastian Graf at 2025-07-14T18:26:32+02:00
CprAnal: Detect recursive newtypes (#25944)
While `cprTransformDataConWork` handles recursive data con workers, it
did not detect the case when a newtype is responsible for the recursion.
This is now detected in the `Cast` case of `cprAnal`.
The same reproducer made it clear that `isRecDataCon` lacked congruent
handling for `AppTy` and `CastTy`, now fixed.
Furthermore, the new repro case T25944 triggered this bug via an
infinite loop in `cprFix`, caused by the infelicity in `isRecDataCon`.
While it should be much less likely to trigger such an infinite loop now
that `isRecDataCon` has been fixed, I made sure to abort the loop after
10 iterations and emitting a warning instead.
Fixes #25944.
- - - - -
1192 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/common.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/hello.hs
- .gitlab/jobs.yaml
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Names.hs
- compiler/GHC/Builtin/Names/TH.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- + compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/InfoTable.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/CmmToAsm.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Dwarf/Constants.hs
- + compiler/GHC/CmmToAsm/LA64.hs
- + compiler/GHC/CmmToAsm/LA64/CodeGen.hs
- + compiler/GHC/CmmToAsm/LA64/Cond.hs
- + compiler/GHC/CmmToAsm/LA64/Instr.hs
- + compiler/GHC/CmmToAsm/LA64/Ppr.hs
- + compiler/GHC/CmmToAsm/LA64/RegInfo.hs
- + compiler/GHC/CmmToAsm/LA64/Regs.hs
- compiler/GHC/CmmToAsm/PIC.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs
- compiler/GHC/CmmToAsm/Reg/Linear.hs
- compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs
- compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs
- + compiler/GHC/CmmToAsm/Reg/Linear/LA64.hs
- compiler/GHC/CmmToAsm/Reg/Target.hs
- compiler/GHC/CmmToAsm/X86/CodeGen.hs
- compiler/GHC/CmmToLlvm/Base.hs
- compiler/GHC/CmmToLlvm/Data.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/ConLike.hs
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Core/DataCon.hs-boot
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Map/Expr.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/CprAnal.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Opt/WorkWrap/Utils.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Predicate.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Core/TyCo/Tidy.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backend.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Config.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- + compiler/GHC/Driver/Session/Inspect.hs
- compiler/GHC/Hs/Binds.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Expr.hs-boot
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Binds.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Monad.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Iface/Type.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Parser/String.hs
- compiler/GHC/Platform/LoongArch64.hs → compiler/GHC/Platform/LA64.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Unbound.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Context.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/Stg/BcPrep.hs
- compiler/GHC/Stg/EnforceEpt/Types.hs
- compiler/GHC/Stg/FVs.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/SysTools/Ar.hs
- compiler/GHC/SysTools/Cpp.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.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/Splice.hs
- compiler/GHC/Tc/Gen/Splice.hs-boot
- compiler/GHC/Tc/Instance/Family.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/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/Solver/Solve.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Instance.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/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.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/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Basic.hs
- − compiler/GHC/Types/Breakpoint.hs
- compiler/GHC/Types/Error.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Hint.hs
- compiler/GHC/Types/Hint/Ppr.hs
- compiler/GHC/Types/Id/Make.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Name/Ppr.hs
- compiler/GHC/Types/Name/Reader.hs
- + compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Types/Tickish.hs
- compiler/GHC/Types/Unique.hs
- compiler/GHC/Types/Var.hs-boot
- compiler/GHC/Unit/Env.hs
- compiler/GHC/Unit/Home/Graph.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/ModGuts.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Expr.hs
- compiler/Language/Haskell/Syntax/Extension.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- + compiler/Language/Haskell/Syntax/ImpExp/IsBoot.hs
- compiler/Language/Haskell/Syntax/Module/Name.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- compiler/Setup.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/exts/control.rst
- docs/users_guide/exts/data_kinds.rst
- docs/users_guide/exts/doandifthenelse.rst
- docs/users_guide/exts/explicit_namespaces.rst
- docs/users_guide/exts/ffi.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/instances.rst
- docs/users_guide/exts/pattern_synonyms.rst
- docs/users_guide/exts/required_type_arguments.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/ghci.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/using-warnings.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- ghc/GHCi/UI/Info.hs
- ghc/GHCi/UI/Monad.hs
- ghc/GHCi/UI/Print.hs
- ghc/Main.hs
- ghc/ghc-bin.cabal.in
- hadrian/README.md
- hadrian/bindist/config.mk.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/doc/flavours.md
- hadrian/doc/user-settings.md
- hadrian/hadrian.cabal
- hadrian/src/Builder.hs
- hadrian/src/Context.hs
- hadrian/src/Context/Path.hs
- hadrian/src/Flavour.hs
- hadrian/src/Flavour/Type.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Ghc.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Flavours/Release.hs
- hadrian/src/Settings/Packages.hs
- hadrian/src/Settings/Program.hs
- hadrian/src/Settings/Warnings.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libffi-tarballs
- libraries/Cabal
- libraries/Win32
- libraries/array
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/base/src/Control/Exception/Backtrace.hs
- libraries/base/src/GHC/JS/Prim/Internal/Build.hs
- libraries/base/src/System/CPUTime/Windows.hsc
- libraries/base/tests/IO/Makefile
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/base/tests/perf/encodingAllocations.hs
- libraries/binary
- libraries/containers
- libraries/deepseq
- libraries/directory
- libraries/exceptions
- libraries/filepath
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/GHC/Compact.hs
- libraries/ghc-compact/GHC/Compact/Serialized.hs
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/System/Mem/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc
- libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/tests/parse_tso_flags.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/jsbits/errno.js
- + libraries/ghc-internal/src/GHC/Internal/AllocationLimitHandler.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Bignum/Integer.hs
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Maybe.hs
- libraries/ghc-internal/src/GHC/Internal/Data/Typeable/Internal.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Backtrace.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs-boot
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- libraries/ghc-internal/src/GHC/Internal/List.hs
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/ghc-internal/src/GHC/Internal/Type/Reflection.hs
- libraries/ghc-internal/src/GHC/Internal/TypeLits.hs
- libraries/ghc-internal/src/GHC/Internal/TypeNats.hs
- libraries/ghc-internal/src/GHC/Internal/Wasm/Prim/Types.hs
- libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal
- libraries/ghc-prim/changelog.md
- libraries/ghc-prim/ghc-prim.cabal
- + libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/changelog.md
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/text
- libraries/unix
- linters/lint-whitespace/lint-whitespace.cabal
- llvm-targets
- m4/fp_cc_supports_target.m4
- m4/fp_gcc_supports_no_pie.m4
- m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4
- m4/fptools_set_c_ld_flags.m4
- m4/fptools_set_platform_vars.m4
- m4/ghc_tables_next_to_code.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- + rts/AllocArray.c
- + rts/AllocArray.h
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Hash.c
- rts/Hash.h
- rts/Heap.c
- rts/Interpreter.c
- rts/Interpreter.h
- rts/Linker.c
- rts/LinkerInternals.h
- rts/PathUtils.c
- rts/PathUtils.h
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/RtsUtils.c
- rts/Schedule.c
- rts/StgCRun.c
- rts/StgMiscClosures.cmm
- rts/ThreadLabels.c
- rts/Threads.c
- rts/Weak.c
- rts/external-symbols.list.in
- rts/include/Rts.h
- rts/include/rts/Bytecodes.h
- rts/include/rts/Constants.h
- rts/include/rts/prof/CCS.h
- rts/include/rts/storage/Closures.h
- rts/include/rts/storage/GC.h
- rts/include/rts/storage/Heap.h
- rts/include/rts/storage/TSO.h
- rts/include/stg/MachRegs.h
- rts/include/stg/MiscClosures.h
- rts/linker/Elf.c
- rts/linker/LoadArchive.c
- rts/linker/LoadNativeObjPosix.c
- rts/linker/MachO.c
- rts/linker/PEi386.c
- rts/linker/PEi386.h
- + rts/linker/ProddableBlocks.c
- + rts/linker/ProddableBlocks.h
- rts/rts.cabal
- rts/sm/Storage.c
- rts/sm/Storage.h
- rts/win32/veh_excn.c
- testsuite/driver/testlib.py
- 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/backpack/cabal/bkpcabal08/bkpcabal08.stdout
- testsuite/tests/bytecode/T22376/all.T
- + testsuite/tests/bytecode/T25975.hs
- + testsuite/tests/bytecode/T25975.stdout
- testsuite/tests/bytecode/all.T
- testsuite/tests/callarity/unittest/CallArity1.hs
- + testsuite/tests/cmm/should_run/T25601.hs
- + testsuite/tests/cmm/should_run/T25601.stdout
- + testsuite/tests/cmm/should_run/T25601a.cmm
- testsuite/tests/cmm/should_run/all.T
- + testsuite/tests/codeGen/should_run/T26061.hs
- + testsuite/tests/codeGen/should_run/T26061.stdout
- testsuite/tests/codeGen/should_run/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- + testsuite/tests/cpranal/sigs/T25944.hs
- + testsuite/tests/cpranal/sigs/T25944.stderr
- testsuite/tests/cpranal/sigs/all.T
- testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr
- testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/dependent/should_fail/T11471.stderr
- testsuite/tests/dependent/should_fail/T13135_simple.stderr
- testsuite/tests/dependent/should_fail/T16326_Fail6.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/diagnostic-codes/codes.stdout
- testsuite/tests/driver/Makefile
- testsuite/tests/driver/RecompExports/RecompExports1.stderr
- testsuite/tests/driver/RecompExports/RecompExports4.stderr
- + testsuite/tests/driver/T4437.stdout
- testsuite/tests/driver/T8526/T8526.stdout
- testsuite/tests/driver/all.T
- testsuite/tests/driver/fat-iface/fat014.stdout
- testsuite/tests/driver/json.stderr
- testsuite/tests/driver/json2.stderr
- testsuite/tests/driver/json_warn.stderr
- testsuite/tests/driver/multipleHomeUnits/multiGHCi.stderr
- testsuite/tests/ffi/should_run/all.T
- testsuite/tests/gadt/T19847a.stderr
- + testsuite/tests/gadt/T23298.hs
- + testsuite/tests/gadt/T23298.stderr
- testsuite/tests/gadt/all.T
- + testsuite/tests/ghc-api/T26120.hs
- + testsuite/tests/ghc-api/T26120.stdout
- testsuite/tests/ghc-api/T6145.hs
- testsuite/tests/ghc-api/all.T
- testsuite/tests/ghc-api/annotations-literals/literals.hs
- testsuite/tests/ghc-api/annotations-literals/parsed.hs
- testsuite/tests/ghc-api/apirecomp001/myghc.hs
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/ghc-api/fixed-nodes/T1.hs
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/ghc-e/should_fail/T18441fail5.stderr
- + testsuite/tests/ghci.debugger/scripts/T26042b.hs
- + testsuite/tests/ghci.debugger/scripts/T26042b.script
- + testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042c.hs
- + testsuite/tests/ghci.debugger/scripts/T26042c.script
- + testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042d.hs
- + testsuite/tests/ghci.debugger/scripts/T26042d.script
- + testsuite/tests/ghci.debugger/scripts/T26042d.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042e.hs
- + testsuite/tests/ghci.debugger/scripts/T26042e.script
- + testsuite/tests/ghci.debugger/scripts/T26042e.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042f.hs
- + testsuite/tests/ghci.debugger/scripts/T26042f.script
- + testsuite/tests/ghci.debugger/scripts/T26042f1.stderr
- + testsuite/tests/ghci.debugger/scripts/T26042f1.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042g.hs
- + testsuite/tests/ghci.debugger/scripts/T26042g.script
- + testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/Makefile
- + testsuite/tests/ghci.debugger/scripts/break031/a/A.hs
- + testsuite/tests/ghci.debugger/scripts/break031/all.T
- + testsuite/tests/ghci.debugger/scripts/break031/b/B.hs
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031a.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.script
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stderr
- + testsuite/tests/ghci.debugger/scripts/break031/break031b.stdout
- + testsuite/tests/ghci.debugger/scripts/break031/unitA
- + testsuite/tests/ghci.debugger/scripts/break031/unitB
- + testsuite/tests/ghci/all.T
- + testsuite/tests/ghci/ghci-mem-primops.hs
- + testsuite/tests/ghci/ghci-mem-primops.script
- + testsuite/tests/ghci/ghci-mem-primops.stdout
- testsuite/tests/ghci/linking/dyn/T3372.hs
- + testsuite/tests/ghci/prog-mhu001/Makefile
- + testsuite/tests/ghci/prog-mhu001/all.T
- + testsuite/tests/ghci/prog-mhu001/e/E.hs
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001a.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001b.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001c.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001d.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001e.stdout
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.script
- + testsuite/tests/ghci/prog-mhu001/prog-mhu001f.stdout
- + testsuite/tests/ghci/prog-mhu001/unitE
- + testsuite/tests/ghci/prog-mhu001/unitE-main-is
- + testsuite/tests/ghci/prog-mhu002/Makefile
- + testsuite/tests/ghci/prog-mhu002/a/A.hs
- + testsuite/tests/ghci/prog-mhu002/all.T
- + testsuite/tests/ghci/prog-mhu002/b/B.hs
- + testsuite/tests/ghci/prog-mhu002/c/C.hs
- + testsuite/tests/ghci/prog-mhu002/d/Main.hs
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002a.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stderr
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002b.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002c.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002d.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002e.stdout
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.script
- + testsuite/tests/ghci/prog-mhu002/prog-mhu002f.stdout
- + testsuite/tests/ghci/prog-mhu002/unitA
- + testsuite/tests/ghci/prog-mhu002/unitB
- + testsuite/tests/ghci/prog-mhu002/unitC
- + testsuite/tests/ghci/prog-mhu002/unitD
- + testsuite/tests/ghci/prog-mhu003/Makefile
- + testsuite/tests/ghci/prog-mhu003/a/A.hs
- + testsuite/tests/ghci/prog-mhu003/all.T
- + testsuite/tests/ghci/prog-mhu003/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/c/C.hs
- + testsuite/tests/ghci/prog-mhu003/d/Foo.hs
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.script
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stderr
- + testsuite/tests/ghci/prog-mhu003/prog-mhu003.stdout
- + testsuite/tests/ghci/prog-mhu003/unitA
- + testsuite/tests/ghci/prog-mhu003/unitB
- + testsuite/tests/ghci/prog-mhu003/unitC
- + testsuite/tests/ghci/prog-mhu003/unitD
- + testsuite/tests/ghci/prog-mhu004/Makefile
- + testsuite/tests/ghci/prog-mhu004/a/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/all.T
- + testsuite/tests/ghci/prog-mhu004/b/Foo.hs
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stderr
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004a.stdout
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.script
- + testsuite/tests/ghci/prog-mhu004/prog-mhu004b.stdout
- + testsuite/tests/ghci/prog-mhu004/unitA
- + testsuite/tests/ghci/prog-mhu004/unitB
- + testsuite/tests/ghci/prog-mhu005/Makefile
- + testsuite/tests/ghci/prog-mhu005/a/A.hs
- + testsuite/tests/ghci/prog-mhu005/all.T
- + testsuite/tests/ghci/prog-mhu005/b/B.hs
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.script
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stderr
- + testsuite/tests/ghci/prog-mhu005/prog-mhu005a.stdout
- + testsuite/tests/ghci/prog-mhu005/unitA
- + testsuite/tests/ghci/prog-mhu005/unitB
- testsuite/tests/ghci/prog010/ghci.prog010.script
- testsuite/tests/ghci/prog018/prog018.stdout
- + testsuite/tests/ghci/prog020/A.hs
- + testsuite/tests/ghci/prog020/B.hs
- + testsuite/tests/ghci/prog020/Makefile
- + testsuite/tests/ghci/prog020/all.T
- + testsuite/tests/ghci/prog020/ghci.prog020.script
- + testsuite/tests/ghci/prog020/ghci.prog020.stderr
- + testsuite/tests/ghci/prog020/ghci.prog020.stdout
- + testsuite/tests/ghci/prog021/A.hs
- + testsuite/tests/ghci/prog021/B.hs
- + testsuite/tests/ghci/prog021/Makefile
- + testsuite/tests/ghci/prog021/all.T
- + testsuite/tests/ghci/prog021/prog021a.script
- + testsuite/tests/ghci/prog021/prog021a.stderr
- + testsuite/tests/ghci/prog021/prog021a.stdout
- + testsuite/tests/ghci/prog021/prog021b.script
- + testsuite/tests/ghci/prog021/prog021b.stderr
- + testsuite/tests/ghci/prog021/prog021b.stdout
- + testsuite/tests/ghci/prog022/A.hs
- + testsuite/tests/ghci/prog022/B.hs
- + testsuite/tests/ghci/prog022/Makefile
- + testsuite/tests/ghci/prog022/all.T
- + testsuite/tests/ghci/prog022/ghci.prog022a.script
- + testsuite/tests/ghci/prog022/ghci.prog022a.stderr
- + testsuite/tests/ghci/prog022/ghci.prog022a.stdout
- + testsuite/tests/ghci/prog022/ghci.prog022b.script
- + testsuite/tests/ghci/prog022/ghci.prog022b.stderr
- + testsuite/tests/ghci/prog022/ghci.prog022b.stdout
- + testsuite/tests/ghci/scripts/GhciPackageRename.hs
- + testsuite/tests/ghci/scripts/GhciPackageRename.script
- + testsuite/tests/ghci/scripts/GhciPackageRename.stdout
- testsuite/tests/ghci/scripts/T12550.stdout
- testsuite/tests/ghci/scripts/T13869.stdout
- testsuite/tests/ghci/scripts/T13997.stdout
- testsuite/tests/ghci/scripts/T17669.stdout
- testsuite/tests/ghci/scripts/T18330.stdout
- testsuite/tests/ghci/scripts/T1914.stdout
- testsuite/tests/ghci/scripts/T20217.stdout
- testsuite/tests/ghci/scripts/T20587.stdout
- testsuite/tests/ghci/scripts/T21110.stderr
- testsuite/tests/ghci/scripts/T6105.stdout
- testsuite/tests/ghci/scripts/T8042.stdout
- testsuite/tests/ghci/scripts/T8042recomp.stdout
- testsuite/tests/ghci/scripts/T8959b.stderr
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/ghci/scripts/ghci021.stderr
- testsuite/tests/ghci/scripts/ghci024.stdout
- testsuite/tests/ghci/scripts/ghci024.stdout-mingw32
- testsuite/tests/ghci/scripts/ghci058.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.script
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stderr
- + testsuite/tests/ghci/scripts/print-unicode-syntax.stdout
- testsuite/tests/ghci/should_run/T11825.stdout
- testsuite/tests/ghci/should_run/TopEnvIface.stdout
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/haddock/should_compile_flag_haddock/T17544_kw.stderr
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.hs
- + testsuite/tests/hiefile/should_run/HieGadtConSigs.stdout
- testsuite/tests/hiefile/should_run/all.T
- testsuite/tests/hpc/fork/hpc_fork.stdout
- testsuite/tests/hpc/function/tough.stdout
- testsuite/tests/hpc/function2/tough2.stdout
- + testsuite/tests/hpc/recsel/Makefile
- + testsuite/tests/hpc/recsel/recsel.hs
- + testsuite/tests/hpc/recsel/recsel.stdout
- + testsuite/tests/hpc/recsel/test.T
- testsuite/tests/hpc/simple/hpc001.stdout
- 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/indexed-types/should_fail/T26176.hs
- + testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/T3330c.stderr
- testsuite/tests/indexed-types/should_fail/T4174.stderr
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- testsuite/tests/indexed-types/should_fail/T9662.stderr
- testsuite/tests/indexed-types/should_fail/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-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- 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/lib/integer/T26017.hs
- + testsuite/tests/lib/integer/T26017.stdout
- testsuite/tests/lib/integer/all.T
- testsuite/tests/lib/integer/integerRecipMod.hs
- testsuite/tests/lib/integer/integerRecipMod.stdout
- testsuite/tests/linear/should_fail/LinearTHFail.stderr
- testsuite/tests/linters/notes.stdout
- testsuite/tests/module/T21826.stderr
- testsuite/tests/module/mod185.stderr
- testsuite/tests/module/mod81.stderr
- testsuite/tests/module/mod91.stderr
- testsuite/tests/numeric/should_run/all.T
- testsuite/tests/numeric/should_run/foundation.hs
- testsuite/tests/numeric/should_run/foundation.stdout
- 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/parser/should_compile/T15323.stderr
- + testsuite/tests/parser/should_compile/T25900.hs
- + testsuite/tests/parser/should_compile/T25900.stderr
- + testsuite/tests/parser/should_compile/T25900_noext.hs
- + testsuite/tests/parser/should_compile/T25900_noext.stderr
- testsuite/tests/parser/should_compile/all.T
- + testsuite/tests/parser/should_run/T25937.hs
- + testsuite/tests/parser/should_run/T25937.stdout
- testsuite/tests/parser/should_run/all.T
- + testsuite/tests/parser/should_run/parser_unit_tests.hs
- 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/partial-sigs/should_fail/T10999.stderr
- testsuite/tests/partial-sigs/should_fail/T14040a.stderr
- testsuite/tests/partial-sigs/should_fail/T14584.stderr
- testsuite/tests/patsyn/should_compile/ImpExp_Exp.hs
- testsuite/tests/patsyn/should_compile/T11959.hs
- testsuite/tests/patsyn/should_compile/T11959.stderr
- testsuite/tests/patsyn/should_compile/T11959Lib.hs
- testsuite/tests/patsyn/should_compile/T13350/boolean/Boolean.hs
- testsuite/tests/patsyn/should_compile/T22521.hs
- testsuite/tests/patsyn/should_compile/T9857.hs
- testsuite/tests/patsyn/should_compile/export.hs
- testsuite/tests/perf/compiler/hard_hole_fits.stderr
- testsuite/tests/perf/should_run/ByteCodeAsm.hs
- testsuite/tests/pmcheck/complete_sigs/T25115a.hs
- testsuite/tests/pmcheck/should_compile/T11822.hs
- testsuite/tests/polykinds/T14172.stderr
- testsuite/tests/polykinds/T14270.hs
- testsuite/tests/polykinds/T14846.stderr
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/printer/T18791.stderr
- testsuite/tests/profiling/should_run/caller-cc/all.T
- testsuite/tests/quasiquotation/T3953.stderr
- testsuite/tests/quasiquotation/T7918.hs
- 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/LiftErrMsg.hs
- + testsuite/tests/quotes/LiftErrMsg.stderr
- + testsuite/tests/quotes/LiftErrMsgDefer.hs
- + testsuite/tests/quotes/LiftErrMsgDefer.stderr
- + testsuite/tests/quotes/LiftErrMsgTyped.hs
- + testsuite/tests/quotes/LiftErrMsgTyped.stderr
- + testsuite/tests/quotes/QQError.hs
- + testsuite/tests/quotes/QQError.stderr
- testsuite/tests/quotes/T10384.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/quotes/TH_localname.stderr
- testsuite/tests/quotes/all.T
- testsuite/tests/rebindable/DoRestrictedM.hs
- testsuite/tests/rename/should_compile/T12548.hs
- + testsuite/tests/rename/should_compile/T22581c.hs
- + testsuite/tests/rename/should_compile/T22581c_helper.hs
- + testsuite/tests/rename/should_compile/T22581d.script
- + testsuite/tests/rename/should_compile/T22581d.stdout
- + testsuite/tests/rename/should_compile/T25899a.hs
- + testsuite/tests/rename/should_compile/T25899b.hs
- + testsuite/tests/rename/should_compile/T25899c.hs
- + testsuite/tests/rename/should_compile/T25899c_helper.hs
- + testsuite/tests/rename/should_compile/T25899d.script
- + testsuite/tests/rename/should_compile/T25899d.stdout
- + testsuite/tests/rename/should_compile/T25983a.hs
- + testsuite/tests/rename/should_compile/T25983a.stderr
- + testsuite/tests/rename/should_compile/T25983b.hs
- + testsuite/tests/rename/should_compile/T25983b.stderr
- + testsuite/tests/rename/should_compile/T25983c.hs
- + testsuite/tests/rename/should_compile/T25983c.stderr
- + testsuite/tests/rename/should_compile/T25983d.hs
- + testsuite/tests/rename/should_compile/T25983d.stderr
- + testsuite/tests/rename/should_compile/T25983e.hs
- + testsuite/tests/rename/should_compile/T25983e.stderr
- + testsuite/tests/rename/should_compile/T25983f.hs
- + testsuite/tests/rename/should_compile/T25983f.stderr
- + testsuite/tests/rename/should_compile/T25983g.hs
- + testsuite/tests/rename/should_compile/T25983g.stderr
- + testsuite/tests/rename/should_compile/T25984a.hs
- + testsuite/tests/rename/should_compile/T25984a.stderr
- + testsuite/tests/rename/should_compile/T25984a_helper.hs
- + testsuite/tests/rename/should_compile/T25991a.hs
- + testsuite/tests/rename/should_compile/T25991a_helper.hs
- testsuite/tests/rename/should_compile/all.T
- + testsuite/tests/rename/should_fail/T22581a.hs
- + testsuite/tests/rename/should_fail/T22581a.stderr
- + testsuite/tests/rename/should_fail/T22581a_helper.hs
- + testsuite/tests/rename/should_fail/T22581b.hs
- + testsuite/tests/rename/should_fail/T22581b.stderr
- + testsuite/tests/rename/should_fail/T22581b_helper.hs
- testsuite/tests/rename/should_fail/T25056.stderr
- testsuite/tests/rename/should_fail/T25056a.hs
- + testsuite/tests/rename/should_fail/T25899e1.hs
- + testsuite/tests/rename/should_fail/T25899e1.stderr
- + testsuite/tests/rename/should_fail/T25899e2.hs
- + testsuite/tests/rename/should_fail/T25899e2.stderr
- + testsuite/tests/rename/should_fail/T25899e3.hs
- + testsuite/tests/rename/should_fail/T25899e3.stderr
- + testsuite/tests/rename/should_fail/T25899e_helper.hs
- + testsuite/tests/rename/should_fail/T25899f.hs
- + testsuite/tests/rename/should_fail/T25899f.stderr
- + testsuite/tests/rename/should_fail/T25899f_helper.hs
- + testsuite/tests/rename/should_fail/T25984b.hs
- + testsuite/tests/rename/should_fail/T25984b.stderr
- + testsuite/tests/rename/should_fail/T25991b1.hs
- + testsuite/tests/rename/should_fail/T25991b1.stderr
- + testsuite/tests/rename/should_fail/T25991b2.hs
- + testsuite/tests/rename/should_fail/T25991b2.stderr
- + testsuite/tests/rename/should_fail/T25991b_helper.hs
- testsuite/tests/rename/should_fail/T9006.stderr
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rep-poly/RepPolyArgument.stderr
- testsuite/tests/rep-poly/RepPolyBackpack1.stderr
- testsuite/tests/rep-poly/RepPolyBinder.stderr
- testsuite/tests/rep-poly/RepPolyDoBind.stderr
- testsuite/tests/rep-poly/RepPolyDoBody1.stderr
- testsuite/tests/rep-poly/RepPolyDoBody2.stderr
- testsuite/tests/rep-poly/RepPolyLeftSection2.stderr
- testsuite/tests/rep-poly/RepPolyMagic.stderr
- testsuite/tests/rep-poly/RepPolyMcBind.stderr
- testsuite/tests/rep-poly/RepPolyMcBody.stderr
- testsuite/tests/rep-poly/RepPolyMcGuard.stderr
- testsuite/tests/rep-poly/RepPolyNPlusK.stderr
- testsuite/tests/rep-poly/RepPolyPatBind.stderr
- testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr
- testsuite/tests/rep-poly/RepPolyRightSection.stderr
- testsuite/tests/rep-poly/RepPolyRule1.stderr
- testsuite/tests/rep-poly/RepPolyTuple.stderr
- testsuite/tests/rep-poly/RepPolyTuple4.stderr
- testsuite/tests/rep-poly/RepPolyTupleSection.stderr
- testsuite/tests/rep-poly/RepPolyWrappedVar.stderr
- testsuite/tests/rep-poly/T11473.stderr
- testsuite/tests/rep-poly/T12709.stderr
- testsuite/tests/rep-poly/T12973.stderr
- testsuite/tests/rep-poly/T13233.stderr
- testsuite/tests/rep-poly/T13929.stderr
- testsuite/tests/rep-poly/T14561.stderr
- testsuite/tests/rep-poly/T14561b.stderr
- testsuite/tests/rep-poly/T17817.stderr
- testsuite/tests/rep-poly/T19615.stderr
- testsuite/tests/rep-poly/T19709b.stderr
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/T23903.stderr
- + testsuite/tests/rep-poly/T26107.hs
- testsuite/tests/rep-poly/UnliftedNewtypesCoerceFail.stderr
- testsuite/tests/rep-poly/all.T
- 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/rts/T22859.hs
- + testsuite/tests/rts/T22859.stderr
- + testsuite/tests/rts/TestProddableBlockSet.c
- testsuite/tests/rts/all.T
- 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/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/T15186.hs
- testsuite/tests/simplCore/should_compile/T15186A.hs
- testsuite/tests/simplCore/should_compile/T23307c.stderr
- + testsuite/tests/simplCore/should_compile/T25703.hs
- + testsuite/tests/simplCore/should_compile/T25703.stderr
- + testsuite/tests/simplCore/should_compile/T25703a.hs
- + testsuite/tests/simplCore/should_compile/T25703a.stderr
- + testsuite/tests/simplCore/should_compile/T25883.hs
- + testsuite/tests/simplCore/should_compile/T25883.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883b.hs
- + testsuite/tests/simplCore/should_compile/T25883b.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883c.hs
- + testsuite/tests/simplCore/should_compile/T25883c.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883d.hs
- + testsuite/tests/simplCore/should_compile/T25883d.stderr
- + testsuite/tests/simplCore/should_compile/T25883d_import.hs
- + testsuite/tests/simplCore/should_compile/T25965.hs
- + testsuite/tests/simplCore/should_compile/T25976.hs
- + testsuite/tests/simplCore/should_compile/T3990c.hs
- + testsuite/tests/simplCore/should_compile/T3990c.stdout
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_compile/simpl017.stderr
- testsuite/tests/simplCore/should_fail/T25672.stderr
- + testsuite/tests/simplCore/should_run/T23429.hs
- + testsuite/tests/simplCore/should_run/T23429.stdout
- testsuite/tests/simplCore/should_run/all.T
- + 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/SI25.hs
- + testsuite/tests/splice-imports/SI25.stderr
- + testsuite/tests/splice-imports/SI25Helper.hs
- + testsuite/tests/splice-imports/SI26.hs
- + testsuite/tests/splice-imports/SI27.hs
- + testsuite/tests/splice-imports/SI27.stderr
- + testsuite/tests/splice-imports/SI28.hs
- + testsuite/tests/splice-imports/SI28.stderr
- + testsuite/tests/splice-imports/SI29.hs
- + testsuite/tests/splice-imports/SI29.stderr
- + testsuite/tests/splice-imports/SI30.script
- + testsuite/tests/splice-imports/SI30.stdout
- + testsuite/tests/splice-imports/SI31.script
- + testsuite/tests/splice-imports/SI31.stderr
- + testsuite/tests/splice-imports/SI32.script
- + testsuite/tests/splice-imports/SI32.stdout
- + testsuite/tests/splice-imports/SI33.script
- + testsuite/tests/splice-imports/SI33.stdout
- + testsuite/tests/splice-imports/SI34.hs
- + testsuite/tests/splice-imports/SI34.stderr
- + testsuite/tests/splice-imports/SI34M1.hs
- + testsuite/tests/splice-imports/SI34M2.hs
- + testsuite/tests/splice-imports/SI35.hs
- + testsuite/tests/splice-imports/SI35A.hs
- + testsuite/tests/splice-imports/SI36.hs
- + testsuite/tests/splice-imports/SI36.stderr
- + testsuite/tests/splice-imports/SI36_A.hs
- + testsuite/tests/splice-imports/SI36_B1.hs
- + testsuite/tests/splice-imports/SI36_B2.hs
- + testsuite/tests/splice-imports/SI36_B3.hs
- + testsuite/tests/splice-imports/SI36_C1.hs
- + testsuite/tests/splice-imports/SI36_C2.hs
- + testsuite/tests/splice-imports/SI36_C3.hs
- + testsuite/tests/splice-imports/all.T
- + testsuite/tests/th/GadtConSigs_th_dump1.hs
- + testsuite/tests/th/GadtConSigs_th_dump1.stderr
- + testsuite/tests/th/GadtConSigs_th_pprint1.hs
- + testsuite/tests/th/GadtConSigs_th_pprint1.stderr
- + testsuite/tests/th/QQInQuote.hs
- + testsuite/tests/th/QQTopError.hs
- + testsuite/tests/th/QQTopError.stderr
- testsuite/tests/th/T10598_TH.stderr
- testsuite/tests/th/T14681.stderr
- testsuite/tests/th/T15321.stderr
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17804.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/T20868.stdout
- 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/T5508.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Lift.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/th/all.T
- testsuite/tests/th/overloaded/TH_overloaded_constraints_fail.stderr
- testsuite/tests/typecheck/no_skolem_info/T14040.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr
- + testsuite/tests/typecheck/should_compile/T14010.hs
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- + testsuite/tests/typecheck/should_compile/T20873c.hs
- testsuite/tests/typecheck/should_compile/T21023.stderr
- − testsuite/tests/typecheck/should_compile/T22141a.stderr
- − testsuite/tests/typecheck/should_compile/T22141b.stderr
- − testsuite/tests/typecheck/should_compile/T22141c.stderr
- − testsuite/tests/typecheck/should_compile/T22141d.stderr
- − testsuite/tests/typecheck/should_compile/T22141e.stderr
- testsuite/tests/typecheck/should_compile/T23739a.hs
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- + testsuite/tests/typecheck/should_compile/T25992.hs
- + testsuite/tests/typecheck/should_compile/T25992.stderr
- + testsuite/tests/typecheck/should_compile/T26020.hs
- + testsuite/tests/typecheck/should_compile/T26020a.hs
- + testsuite/tests/typecheck/should_compile/T26020a_help.hs
- + testsuite/tests/typecheck/should_compile/T26030.hs
- testsuite/tests/typecheck/should_compile/T7050.stderr
- + testsuite/tests/typecheck/should_compile/TyAppPat_Tricky.hs
- testsuite/tests/typecheck/should_compile/TypeRepCon.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/T16204c.stderr
- testsuite/tests/typecheck/should_fail/T18851.stderr
- testsuite/tests/typecheck/should_fail/T20443b.stderr
- − testsuite/tests/typecheck/should_fail/T20873c.hs
- − testsuite/tests/typecheck/should_fail/T20873c.stderr
- testsuite/tests/typecheck/should_compile/T22141a.hs → testsuite/tests/typecheck/should_fail/T22141a.hs
- testsuite/tests/typecheck/should_fail/T22141a.stderr
- testsuite/tests/typecheck/should_compile/T22141b.hs → testsuite/tests/typecheck/should_fail/T22141b.hs
- testsuite/tests/typecheck/should_fail/T22141b.stderr
- testsuite/tests/typecheck/should_compile/T22141c.hs → testsuite/tests/typecheck/should_fail/T22141c.hs
- testsuite/tests/typecheck/should_fail/T22141c.stderr
- testsuite/tests/typecheck/should_compile/T22141d.hs → testsuite/tests/typecheck/should_fail/T22141d.hs
- testsuite/tests/typecheck/should_fail/T22141d.stderr
- testsuite/tests/typecheck/should_compile/T22141e.hs → testsuite/tests/typecheck/should_fail/T22141e.hs
- testsuite/tests/typecheck/should_fail/T22141e.stderr
- testsuite/tests/typecheck/should_compile/T22141e_Aux.hs → testsuite/tests/typecheck/should_fail/T22141e_Aux.hs
- + testsuite/tests/typecheck/should_fail/T25950.hs
- + testsuite/tests/typecheck/should_fail/T25950.stderr
- + testsuite/tests/typecheck/should_fail/T26004.hs
- + testsuite/tests/typecheck/should_fail/T26004.stderr
- + testsuite/tests/typecheck/should_fail/T26015.hs
- + testsuite/tests/typecheck/should_fail/T26015.stderr
- testsuite/tests/typecheck/should_fail/T3966.stderr
- + testsuite/tests/typecheck/should_fail/T3966b.hs
- + testsuite/tests/typecheck/should_fail/T3966b.stderr
- testsuite/tests/typecheck/should_fail/T7453.stderr
- testsuite/tests/typecheck/should_fail/T7696.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail097.stderr
- + testsuite/tests/typecheck/should_run/T25998.hs
- + testsuite/tests/typecheck/should_run/T25998.stdout
- testsuite/tests/typecheck/should_run/all.T
- testsuite/tests/unboxedsums/unpack_sums_5.stderr
- + testsuite/tests/vdq-rta/should_compile/T25127_data.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_data_inst.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_infix.hs
- + testsuite/tests/vdq-rta/should_compile/T25127_newtype.hs
- testsuite/tests/vdq-rta/should_compile/all.T
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.hs
- testsuite/tests/vdq-rta/should_fail/T23739_fail_case.stderr
- testsuite/tests/vdq-rta/should_fail/T24159_type_syntax_th_fail.script
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_arity.stderr
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.hs
- + testsuite/tests/vdq-rta/should_fail/T25127_fail_th_quote.stderr
- testsuite/tests/vdq-rta/should_fail/all.T
- testsuite/tests/warnings/should_compile/DataToTagWarnings.hs
- testsuite/tests/warnings/should_compile/T14794a.hs
- testsuite/tests/warnings/should_compile/T14794a.stderr
- testsuite/tests/warnings/should_compile/T14794b.hs
- testsuite/tests/warnings/should_compile/T14794b.stderr
- testsuite/tests/warnings/should_compile/T14794c.hs
- testsuite/tests/warnings/should_compile/T14794c.stderr
- testsuite/tests/warnings/should_compile/T14794d.hs
- testsuite/tests/warnings/should_compile/T14794d.stderr
- testsuite/tests/warnings/should_compile/T14794e.hs
- testsuite/tests/warnings/should_compile/T14794e.stderr
- testsuite/tests/warnings/should_compile/T14794f.hs
- testsuite/tests/warnings/should_compile/T14794f.stderr
- testsuite/tests/wcompat-warnings/Template.hs
- + testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/genprimopcode/Main.hs
- utils/genprimopcode/Syntax.hs
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/CHANGES.md
- utils/haddock/doc/cheatsheet/haddocks.md
- utils/haddock/doc/markup.rst
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-api/resources/html/Linuwial.std-theme/linuwial.css
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.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/Backends/Xhtml/Utils.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface.hs
- utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/Interface/LexParseRn.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs
- utils/haddock/haddock-library/test/Documentation/Haddock/ParserSpec.hs
- utils/haddock/haddock-test/haddock-test.cabal
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs
- utils/haddock/haddock.cabal
- utils/haddock/html-test/ref/Bug1004.html
- + utils/haddock/html-test/ref/Bug25739.html
- utils/haddock/html-test/ref/Bug548.html
- utils/haddock/html-test/ref/Bug973.html
- utils/haddock/html-test/ref/Hash.html
- utils/haddock/html-test/ref/ImplicitParams.html
- utils/haddock/html-test/ref/Instances.html
- utils/haddock/html-test/ref/PatternSyns.html
- + utils/haddock/html-test/ref/RedactTypeSynonyms.html
- utils/haddock/html-test/ref/TypeOperators.html
- + utils/haddock/html-test/src/Bug25739.hs
- + utils/haddock/html-test/src/RedactTypeSynonyms.hs
- utils/haddock/html-test/src/TypeOperators.hs
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
- + utils/haddock/latex-test/ref/RedactTypeSynonyms/RedactTypeSynonyms.tex
- + utils/haddock/latex-test/src/RedactTypeSynonyms/RedactTypeSynonyms.hs
- utils/hpc
- utils/hsc2hs
- utils/iserv/iserv.cabal.in
- utils/llvm-targets/gen-data-layout.sh
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6425a1f063df92bc9a50870bb7e377…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6425a1f063df92bc9a50870bb7e377…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Simon Peyton Jones pushed to branch wip/T20264 at Glasgow Haskell Compiler / GHC
Commits:
7fe3be18 by Simon Peyton Jones at 2025-07-14T17:21:38+01:00
More small fixes
- - - - -
3 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/SpecConstr.hs
- compiler/GHC/Core/Type.hs
Changes:
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -2228,8 +2228,7 @@ occ_anal_lam_tail env expr@(Lam {})
= addInScope env (reverse rev_bndrs) $ \env ->
let !(WUD usage body') = occ_anal_lam_tail env body
wrap_lam body bndr = Lam (tagLamBinder usage bndr) body
- in WUD (usage `addLamTyCoVarOccs` rev_bndrs)
- (foldl' wrap_lam body' rev_bndrs)
+ in WUD usage (foldl' wrap_lam body' rev_bndrs)
-- For casts, keep going in the same lambda-group
-- See Note [Occurrence analysis for lambda binders]
@@ -3136,12 +3135,15 @@ addInScopeOne env bndr = addInScope env [bndr]
addInScope :: OccEnv -> [Var]
-> (OccEnv -> WithUsageDetails a) -> WithUsageDetails a
{-# INLINE addInScope #-}
+-- Do occ-analysis under a telescope of binders
+-- `addInScope` accounts for
+-- -- Accounting for the free vars of the types of the binders
+-- - Dealing with the interaction between shadowing and
+-- the `bad_join` and binder-swap mechanisms
-- This function is called a lot, so we want to inline the fast path
--- so we don't have to allocate thing_inside and call it
+-- so we don't have to allocate thing_inside and call it
-- The bndrs must include TyVars as well as Ids, because of
-- (BS3) in Note [Binder swap]
--- We do not assume that the bndrs are in scope order; in fact the
--- call in occ_anal_lam_tail gives them to addInScope in /reverse/ order
addInScope env bndrs thing_inside
| null bndrs -- E.g. nullary constructors in a `case`
@@ -3789,15 +3791,6 @@ addTyCoOccs :: UsageDetails -> TyCoOccEnv -> UsageDetails
addTyCoOccs uds@(UD { ud_tyco_env = env}) extras
= uds { ud_tyco_env = env `plusTyCoOccEnv` extras }
-addLamTyCoVarOccs :: UsageDetails -> [Var] -> UsageDetails
--- occAnalLamBndrs :: OccEnv -> UsageDetails -> [Var] -> WithUsageDetails [Var]
--- Add any TyCoVars free in the type of a lambda-binder
--- See Note [Gather occurrences of coercion variables]
-addLamTyCoVarOccs uds bndrs
- = foldr add uds bndrs
- where
- add bndr uds = uds `addManyOccs` tyCoVarsOfType (varType bndr)
-
emptyDetails :: UsageDetails
emptyDetails = UD { ud_id_env = emptyVarEnv
, ud_z_many = emptyVarEnv
=====================================
compiler/GHC/Core/Opt/SpecConstr.hs
=====================================
@@ -2679,8 +2679,8 @@ argToPat1 :: ScEnv
-> ArgOcc
-> StrictnessMark
-> UniqSM (Bool, Expr CoreBndr, [Id])
-argToPat1 _env _in_scope _val_env arg@(Type {}) _arg_occ _arg_str
- = return (False, arg, [])
+argToPat1 _env in_scope _val_env (Type ty) _arg_occ _arg_str
+ = return (False, Type (mkTyPat in_scope ty), [])
argToPat1 env in_scope val_env (Tick _ arg) arg_occ arg_str
= argToPat env in_scope val_env arg arg_occ arg_str
@@ -2819,8 +2819,19 @@ argToPat in_scope val_env arg arg_occ
-- The default case: make a wild-card
-- We use this for coercions too
-argToPat1 _env _in_scope _val_env arg _arg_occ arg_str
- = wildCardPat (exprType arg) arg_str
+argToPat1 _env in_scope _val_env arg _arg_occ arg_str
+ = wildCardPat (mkTyPat in_scope (exprType arg)) arg_str
+
+mkTyPat :: InScopeSet -> Type -> Type
+-- Expand unfoldings of any tyvars not in the in-scope set
+-- E.g. call f @a @b{=a} (K @a)
+-- The tyvars `a` and `b` might have been in scope at the call site,
+-- but not at the definition site. We want a call pattern
+-- f @a @a (K @a) a
+mkTyPat in_scope ty
+ = expandSomeTyVarUnfoldings not_in_scope ty
+ where
+ not_in_scope tv = not (tv `elemInScopeSet` in_scope)
-- | wildCardPats are always boring
wildCardPat :: Type -> StrictnessMark -> UniqSM (Bool, CoreArg, [Id])
=====================================
compiler/GHC/Core/Type.hs
=====================================
@@ -171,7 +171,8 @@ module GHC.Core.Type (
anyFreeVarsOfType, anyFreeVarsOfTypes,
noFreeVarsOfType,
expandTypeSynonyms, expandSynTyConApp_maybe,
- typeSize, occCheckExpand, expandTyVarUnfoldings,
+ typeSize, occCheckExpand,
+ expandTyVarUnfoldings, expandSomeTyVarUnfoldings,
-- ** Closing over kinds
closeOverKindsDSet, closeOverKindsList,
@@ -491,7 +492,7 @@ on its fast path must also be inlined, linked back to this Note.
* *
********************************************************************* -}
-expandTyVarUnfoldings :: TyVarSet -> Type -> Type
+expandTyVarUnfoldings :: TyVarSet -> Type -> Type
-- (expandTyVarUnfoldings tvs ty) replace any occurrences of `tvs` in `ty`
-- with their unfoldings. The returned type does not mention any of `tvs`.
--
@@ -500,7 +501,11 @@ expandTyVarUnfoldings :: TyVarSet -> Type -> Type
-- also in scope, without having been shadowed.
expandTyVarUnfoldings tvs ty
| isEmptyVarSet tvs = ty
- | otherwise = runIdentity (expand ty)
+ | otherwise = expandSomeTyVarUnfoldings (`elemVarSet` tvs) ty
+
+expandSomeTyVarUnfoldings :: (TyVar -> Bool) -> Type -> Type
+expandSomeTyVarUnfoldings expand_me ty
+ = runIdentity (expand ty)
where
expand :: Type -> Identity Type
(expand, _, _, _)
@@ -508,8 +513,8 @@ expandTyVarUnfoldings tvs ty
, tcm_hole = exp_hole, tcm_tycobinder = exp_tcb
, tcm_tycon = pure })
exp_tv _ tv = case tyVarUnfolding_maybe tv of
- Just ty | tv `elemVarSet` tvs -> expand ty
- _ -> pure (TyVarTy tv)
+ Just ty | expand_me tv -> expand ty
+ _ -> pure (TyVarTy tv)
exp_cv _ cv = pure (CoVarCo cv)
exp_hole _ cv = pprPanic "expand_tv_unf" (ppr cv)
exp_tcb :: () -> TyCoVar -> ForAllTyFlag -> (() -> TyCoVar -> Identity r) -> Identity r
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7fe3be18a1bdab4b78b5264baea3dcd…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7fe3be18a1bdab4b78b5264baea3dcd…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/step-out-10] 19 commits: Implement user-defined allocation limit handlers
by Rodrigo Mesquita (@alt-romes) 14 Jul '25
by Rodrigo Mesquita (@alt-romes) 14 Jul '25
14 Jul '25
Rodrigo Mesquita pushed to branch wip/romes/step-out-10 at Glasgow Haskell Compiler / GHC
Commits:
ea2c6673 by Teo Camarasu at 2025-07-08T13:24:43-04:00
Implement user-defined allocation limit handlers
Allocation Limits allow killing a thread if they allocate more than a
user-specified limit.
We extend this feature to allow more versatile behaviour.
- We allow not killing the thread if the limit is exceeded.
- We allow setting a custom handler to be called when the limit is exceeded.
User-specified allocation limit handlers run in a fresh thread and are passed
the ThreadId of the thread that exceeded its limit.
We introduce utility functions for getting and setting the allocation
limits of other threads, so that users can reset the limit of a thread
from a handler. Both of these are somewhat coarse-grained as we are
unaware of the allocations in the current nursery chunk.
We provide several examples of usages in testsuite/tests/rts/T22859.hs
Resolves #22859
- - - - -
03e047f9 by Simon Hengel at 2025-07-08T13:25:25-04:00
Fix typo in using.rst
- - - - -
67957854 by Ben Gamari at 2025-07-09T09:44:44-04:00
compiler: Import AnnotationWrapper from ghc-internal
Since `GHC.Desugar` exported from `base` has been deprecated.
- - - - -
813d99d6 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-compact: Eliminate dependency on ghc-prim
- - - - -
0ec952a1 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Eliminate dependency on ghc-prim
- - - - -
480074c3 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Drop redundant import
- - - - -
03455829 by Ben Gamari at 2025-07-09T09:44:45-04:00
ghc-prim: Bump version to 0.13.1
There are no interface changes from 0.13.0 but the implementation now
lives in `ghc-internal`.
- - - - -
d315345a by Ben Gamari at 2025-07-09T09:44:45-04:00
template-haskell: Bump version number to 2.24.0.0
Bumps exceptions submodule.
- - - - -
004c800e by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump GHC version number to 9.14
- - - - -
eb1a3816 by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump parsec to 3.1.18.0
Bumps parsec submodule.
- - - - -
86f83296 by Ben Gamari at 2025-07-09T09:44:45-04:00
unix: Bump to 2.8.7.0
Bumps unix submodule.
- - - - -
89e13998 by Ben Gamari at 2025-07-09T09:44:45-04:00
binary: Bump to 0.8.9.3
Bumps binary submodule.
- - - - -
55fff191 by Ben Gamari at 2025-07-09T09:44:45-04:00
Win32: Bump to 2.14.2.0
Bumps Win32 submodule.
- - - - -
7dafa40c by Ben Gamari at 2025-07-09T09:44:45-04:00
base: Bump version to 4.22.0
Bumps various submodules.
- - - - -
ef03d8b8 by Rodrigo Mesquita at 2025-07-09T09:45:28-04:00
base: Export displayExceptionWithInfo
This function should be exposed from base following CLC#285
Approved change in CLC#344
Fixes #26058
- - - - -
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
2a1f0d4b by Rodrigo Mesquita at 2025-07-14T16:32:21+01:00
debugger: Uniquely identify breakpoints by internal id
Since b85b11994e0130ff2401dd4bbdf52330e0bcf776 (support inlining
breakpoints), a breakpoint has been identified at runtime by *two* pairs
of <module,index>.
- The first, aka a 'BreakpointId', uniquely identifies a breakpoint in
the source of a module by using the Tick index. A Tick index can index
into ModBreaks.modBreaks_xxx to fetch source-level information about
where that tick originated.
- When a user specifies e.g. a line breakpoint using :break, we'll reverse
engineer what a Tick index for that line
- We update the `BreakArray` of that module (got from the
LoaderState) at that tick index to `breakOn`.
- A BCO we can stop at is headed by a BRK_FUN instruction. This
instruction stores in an operand the `tick index` it is associated
to. We look it up in the associated `BreakArray` (also an operand)
and check wheter it was set to `breakOn`.
- The second, aka the `ibi_info_mod` + `ibi_info_ix` of the
`InternalBreakpointId`, uniquely index into the `imodBreaks_breakInfo`
-- the information we gathered during code generation about the
existing breakpoint *ocurrences*.
- Note that with optimisation there may be many occurrences of the
same source-tick-breakpoint across different modules. The
`ibi_info_ix` is unique per occurrence, but the `bi_tick_ix` may be
shared. See Note [Breakpoint identifiers] about this.
- Note that besides the tick ids, info ids are also stored in
`BRK_FUN` so the break handler can refer to the associated
`CgBreakInfo`.
In light of that, the driving changes come from the desire to have the
info_id uniquely identify the breakpoint at runtime, and the source tick
id being derived from it:
- An InternalBreakpointId should uniquely identify a breakpoint just
from the code-generation identifiers of `ibi_info_ix` and `ibi_info_mod`.
So we drop `ibi_tick_mod` and `ibi_tick_ix`.
- A BRK_FUN instruction need only record the "internal breakpoint id",
not the tick-level id.
So we drop the tick mod and tick index operands.
- A BreakArray should be indexed by InternalBreakpointId rather than
BreakpointId
That means we need to do some more work when setting a breakpoint.
Specifically, we need to figure out the internal ids (occurrences of a
breakpoint) from the source-level BreakpointId we want to set the
breakpoint at (recall :break refers to breaks at the source level).
Besides this change being an improvement to the handling of breakpoints
(it's clearer to have a single unique identifier than two competing
ones), it unlocks the possibility of generating "internal" breakpoints
during Cg (needed for #26042).
It should also be easier to introduce multi-threaded-aware `BreakArrays`
following this change (needed for #26064).
Se also the new Note [ModBreaks vs InternalModBreaks]
- - - - -
91 changed files:
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Monad.hs
- libraries/Win32
- libraries/array
- libraries/base/base.cabal.in
- libraries/base/src/Control/Exception.hs
- libraries/binary
- libraries/deepseq
- libraries/directory
- libraries/exceptions
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/GHC/Compact.hs
- libraries/ghc-compact/GHC/Compact/Serialized.hs
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/System/Mem/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/src/GHC/Internal/AllocationLimitHandler.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-prim/changelog.md
- libraries/ghc-prim/ghc-prim.cabal
- libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/text
- libraries/unix
- rts/Disassembler.c
- rts/Exception.cmm
- rts/Interpreter.c
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/Schedule.c
- rts/external-symbols.list.in
- rts/include/rts/storage/GC.h
- rts/include/rts/storage/TSO.h
- rts/include/stg/MiscClosures.h
- testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
- 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-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- + testsuite/tests/rts/T22859.hs
- + testsuite/tests/rts/T22859.stderr
- testsuite/tests/rts/all.T
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-test/haddock-test.cabal
- utils/haddock/haddock.cabal
- utils/hsc2hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6696180f5e096ed10e72a4cb488861…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6696180f5e096ed10e72a4cb488861…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/spj-apporv-Oct24] - kill ExpectedFunTyOrigin and incorporate it into CtOrigin
by Apoorv Ingle (@ani) 14 Jul '25
by Apoorv Ingle (@ani) 14 Jul '25
14 Jul '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
eb0e4601 by Apoorv Ingle at 2025-07-14T09:35:45-05:00
- kill ExpectedFunTyOrigin and incorporate it into CtOrigin
- fix error message suggestions for record fields
- - - - -
9 changed files:
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Unify.hs
Changes:
=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -24,6 +24,10 @@ import GHC.Driver.Config.Diagnostic
import GHC.Rename.Unbound
+import Language.Haskell.Syntax (DotFieldOcc (..))
+import Language.Haskell.Syntax.Basic (FieldLabelString (..))
+import GHC.Hs.Expr (SrcCodeOrigin (..), HsExpr (..))
+
import GHC.Tc.Types
import GHC.Tc.Utils.Monad
import GHC.Tc.Errors.Types
@@ -2349,7 +2353,7 @@ mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped))
isNothing (lookupLocalRdrOcc lcl_env occ_name)
record_field = case orig of
- GetFieldOrigin name -> Just (mkVarOccFS name)
+ ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ name))) -> Just (mkVarOccFS (field_label $ unLoc $ dfoLabel name))
_ -> Nothing
{- Note [Report candidate instances]
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -857,7 +857,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
-- Rule IARG from Fig 4 of the QL paper:
go1 pos acc fun_ty
(EValArg { ea_arg = arg, ea_ctxt = ctxt } : rest_args)
- = do { let herald = ExpectedFunTyArg (HsExprTcThing tc_fun) (unLoc arg)
+ = do { let herald = ExpectedFunTyArg pos (HsExprTcThing tc_fun) (unLoc arg)
; (wrap, arg_ty, res_ty) <-
-- NB: matchActualFunTy does the rep-poly check.
-- For example, suppose we have f :: forall r (a::TYPE r). a -> Int
@@ -876,7 +876,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
-- Make a fresh nus for each argument in rule IVAR
new_arg_ty (L _ arg) i
= do { arg_nu <- newOpenFlexiFRRTyVarTy $
- FRRExpectedFunTy (ExpectedFunTyArg (HsExprTcThing tc_fun) arg) i
+ FRRExpectedFunTy (ExpectedFunTyArg i (HsExprTcThing tc_fun) arg) i
-- Following matchActualFunTy, we create nu_i :: TYPE kappa_i[conc],
-- thereby ensuring that the arguments have concrete runtime representations
=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -976,7 +976,7 @@ tcSynArgE orig op sigma_ty syn_ty thing_inside
-- fixed RuntimeRep, as needed to call mkWpFun.
; return (result, match_wrapper <.> fun_wrap) }
where
- herald = ExpectedFunTySyntaxOp orig op
+ herald = ExpectedFunTySyntaxOp 1 orig op
go rho_ty (SynType the_ty)
= do { wrap <- tcSubTypePat orig GenSigCtxt the_ty rho_ty
@@ -1005,7 +1005,7 @@ tcSynArgA orig op sigma_ty arg_shapes res_shape thing_inside
thing_inside (arg_results ++ res_results) (map scaledMult arg_tys ++ arg_res_mults)
; return (result, match_wrapper, arg_wrappers, res_wrapper) }
where
- herald = ExpectedFunTySyntaxOp orig op
+ herald = ExpectedFunTySyntaxOp (length arg_shapes) orig op
tc_syn_args_e :: [TcSigmaTypeFRR] -> [SyntaxOpType]
-> ([TcSigmaTypeFRR] -> [Mult] -> TcM a)
=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -655,7 +655,7 @@ tcInferOverLit lit@(OverLit { ol_val = val
; let
thing = NameThing from_name
mb_thing = Just thing
- herald = ExpectedFunTyArg thing (HsLit noExtField hs_lit)
+ herald = ExpectedFunTyArg 1 thing (HsLit noExtField hs_lit)
; (wrap2, sarg_ty, res_ty) <- matchActualFunTy herald mb_thing (1, from_ty) from_ty
; co <- unifyType mb_thing (hsLitType hs_lit) (scaledThing sarg_ty)
=====================================
compiler/GHC/Tc/Gen/Match.hs
=====================================
@@ -118,7 +118,7 @@ tcFunBindMatches ctxt fun_name mult matches invis_pat_tys exp_ty
= assertPpr (funBindPrecondition matches) (pprMatches matches) $
do { -- Check that they all have the same no of arguments
arity <- checkArgCounts matches
-
+ ; let herald = ExpectedFunTyMatches arity (NameThing fun_name) matches
; traceTc "tcFunBindMatches 1" (ppr fun_name $$ ppr mult $$ ppr exp_ty $$ ppr arity)
; (wrap_fun, r)
@@ -138,7 +138,7 @@ tcFunBindMatches ctxt fun_name mult matches invis_pat_tys exp_ty
; return (wrap_fun, r) }
where
mctxt = mkPrefixFunRhs (noLocA fun_name) noAnn
- herald = ExpectedFunTyMatches (NameThing fun_name) matches
+
funBindPrecondition :: MatchGroup GhcRn (LHsExpr GhcRn) -> Bool
funBindPrecondition (MG { mg_alts = L _ alts })
=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -698,7 +698,7 @@ tc_pat pat_ty penv ps_pat thing_inside = case ps_pat of
-- Note [View patterns and polymorphism]
-- Expression must be a function
- ; let herald = ExpectedFunTyViewPat $ unLoc expr
+ ; let herald = ExpectedFunTyViewPat 1 $ unLoc expr
; (expr_wrap1, Scaled _mult inf_arg_ty, inf_res_sigma)
<- matchActualFunTy herald (Just . HsExprRnThing $ unLoc expr) (1,expr_ty) expr_ty
-- See Note [View patterns and polymorphism]
=====================================
compiler/GHC/Tc/Types/ErrCtxt.hs
=====================================
@@ -17,7 +17,7 @@ import GHC.Hs.Extension
import GHC.Parser.Annotation ( LocatedN, SrcSpanAnnA )
import GHC.Tc.Errors.Types.PromotionErr ( TermLevelUseCtxt )
-import GHC.Tc.Types.Origin ( CtOrigin, UserTypeCtxt, ExpectedFunTyOrigin )
+import GHC.Tc.Types.Origin ( CtOrigin, UserTypeCtxt )
import GHC.Tc.Utils.TcType ( TcType, TcTyCon )
import GHC.Tc.Zonk.Monad ( ZonkM )
@@ -120,7 +120,7 @@ data ErrCtxtMsg
-- | In a function application.
| FunAppCtxt !FunAppCtxtFunArg !Int
-- | In a function call.
- | FunTysCtxt !ExpectedFunTyOrigin !Type !Int !Int
+ | FunTysCtxt !CtOrigin !Type !Int !Int
-- | In the result of a function call.
| FunResCtxt !(HsExpr GhcTc) !Int !Type !Type !Int !Int
-- | In the declaration of a type constructor.
=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -21,6 +21,7 @@ module GHC.Tc.Types.Origin (
CtOrigin(..), exprCtOrigin, lexprCtOrigin, matchesCtOrigin, grhssCtOrigin,
srcCodeOriginCtOrigin,
isVisibleOrigin, toInvisibleOrigin,
+ updatePositionCtOrigin,
pprCtOrigin, isGivenOrigin, isWantedWantedFunDepOrigin,
isWantedSuperclassOrigin,
ClsInstOrQC(..), NakedScFlag(..), NonLinearPatternReason(..),
@@ -45,7 +46,7 @@ module GHC.Tc.Types.Origin (
FRRArrowContext(..), pprFRRArrowContext,
-- ** ExpectedFunTy FixedRuntimeRepOrigin
- ExpectedFunTyOrigin(..), pprExpectedFunTyOrigin, pprExpectedFunTyHerald,
+ pprExpectedFunTyHerald,
-- * InstanceWhat
InstanceWhat(..), SafeOverlapping
@@ -82,8 +83,6 @@ import GHC.Utils.Misc( HasDebugCallStack )
import GHC.Types.Unique
import GHC.Types.Unique.Supply
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import qualified Data.Kind as Hs
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
@@ -653,8 +652,67 @@ data CtOrigin
Type -- the instantiated type of the method
| AmbiguityCheckOrigin UserTypeCtxt
| ImplicitLiftOrigin HsImplicitLiftSplice
+
| ExpansionOrigin SrcCodeOrigin -- This is due to an expansion of the original thing given by SrcCodeOrigin
+ -- | A rebindable syntax operator is expected to have a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyDoBind, RepPolyDoBody{1,2}, RepPolyMc{Bind,Body,Guard}, RepPolyNPlusK
+ | forall (p :: Pass)
+ . (OutputableBndrId p)
+ => ExpectedFunTySyntaxOp Int
+ !CtOrigin !(HsExpr (GhcPass p))
+ -- ^ rebindable syntax operator
+
+ -- | A view pattern must have a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyBinder
+ | ExpectedFunTyViewPat Int
+ !(HsExpr GhcRn)
+ -- ^ function used in the view pattern
+
+ -- | Need to be able to extract an argument type from a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyApp
+ | forall (p :: Pass)
+ . Outputable (HsExpr (GhcPass p)) => ExpectedFunTyArg
+ Int
+ -- ^ Argument number
+ !TypedThing
+ -- ^ function
+ !(HsExpr (GhcPass p))
+ -- ^ argument
+
+ -- | Ensure that a function defined by equations indeed has a function type
+ -- with the appropriate number of arguments.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyBinder, RepPolyRecordPattern, RepPolyWildcardPattern
+ | ExpectedFunTyMatches Int
+ !TypedThing
+ -- ^ name of the function
+ !(MatchGroup GhcRn (LHsExpr GhcRn))
+ -- ^ equations
+
+ -- | Ensure that a lambda abstraction has a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyLambda, RepPolyMatch
+ | ExpectedFunTyLam HsLamVariant
+ !(HsExpr GhcRn)
+ -- ^ the entire lambda-case expression
+
+updatePositionCtOrigin :: Int -> CtOrigin -> CtOrigin
+updatePositionCtOrigin i (ExpectedFunTySyntaxOp _ c e) = ExpectedFunTySyntaxOp i c e
+updatePositionCtOrigin i (ExpectedFunTyViewPat _ e) = ExpectedFunTyViewPat i e
+updatePositionCtOrigin i (ExpectedFunTyArg _ t e) = ExpectedFunTyArg i t e
+updatePositionCtOrigin i (ExpectedFunTyMatches _ t e) = ExpectedFunTyMatches i t e
+updatePositionCtOrigin _ c = c
+
+
data NonLinearPatternReason
= LazyPatternReason
| GeneralisedPatternReason
@@ -727,7 +785,8 @@ lexprCtOrigin (L _ e) = exprCtOrigin e
exprCtOrigin :: HsExpr GhcRn -> CtOrigin
exprCtOrigin (HsVar _ (L _ (WithUserRdr _ name))) = OccurrenceOf name
-exprCtOrigin (HsGetField _ _ (L _ f)) = GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
+exprCtOrigin e@(HsGetField _ _ (L _ _)) = ExpansionOrigin (OrigExpr e)
+ -- GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
exprCtOrigin (HsOverLabel _ l) = OverLabelOrigin l
exprCtOrigin (ExplicitList {}) = ListOrigin
exprCtOrigin (HsIPVar _ ip) = IPOccOrigin ip
@@ -739,7 +798,7 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1
exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op
exprCtOrigin (NegApp _ e _) = lexprCtOrigin e
exprCtOrigin (HsPar _ e) = lexprCtOrigin e
-exprCtOrigin (HsProjection _ p) = GetFieldOrigin ((field_label . unLoc . dfoLabel . NE.head . NE.reverse) p)
+exprCtOrigin e@(HsProjection _ _) = ExpansionOrigin (OrigExpr e)
exprCtOrigin (SectionL _ _ _) = SectionOrigin
exprCtOrigin (SectionR _ _ _) = SectionOrigin
exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple"
@@ -802,7 +861,7 @@ pprCtOrigin (ExpansionOrigin o)
where what :: SDoc
what = case o of
OrigStmt{} -> text "a do statement"
- OrigExpr e -> text "an expression" <+> ppr e
+ OrigExpr e -> pprCtO (exprCtOrigin e)
OrigPat p -> text "a pattern" <+> ppr p
pprCtOrigin (GivenSCOrigin sk d blk)
@@ -917,9 +976,38 @@ pprCtOrigin (NonLinearPatternOrigin reason pat)
= hang (ctoHerald <+> text "a non-linear pattern" <+> quotes (ppr pat))
2 (pprNonLinearPatternReason reason)
+pprCtOrigin (ExpectedFunTySyntaxOp i orig op) =
+ vcat [ sep [ the_arg_of i
+ , text "the rebindable syntax operator"
+ , quotes (ppr op) ]
+ , nest 2 (ppr orig) ]
+pprCtOrigin (ExpectedFunTyViewPat i expr) =
+ vcat [ the_arg_of i <+> text "the view pattern"
+ , nest 2 (ppr expr) ]
+pprCtOrigin (ExpectedFunTyArg i fun arg) =
+ sep [ text "The" <+> speakNth i <+> text "argument"
+ , quotes (ppr arg)
+ , text "of"
+ , quotes (ppr fun) ]
+pprCtOrigin (ExpectedFunTyMatches i fun (MG { mg_alts = L _ alts }))
+ | null alts
+ = the_arg_of i <+> quotes (ppr fun)
+ | otherwise
+ = text "The" <+> speakNth i <+> text "pattern in the equation" <> plural alts
+ <+> text "for" <+> quotes (ppr fun)
+pprCtOrigin (ExpectedFunTyLam lam_variant _) = binder_of $ lamCaseKeyword lam_variant
+
pprCtOrigin simple_origin
= ctoHerald <+> pprCtO simple_origin
+
+the_arg_of :: Int -> SDoc
+the_arg_of i = text "The" <+> speakNth i <+> text "argument of"
+
+binder_of :: SDoc -> SDoc
+binder_of what = text "The binder of the" <+> what <+> text "expression"
+
+
-- | Short one-liners
pprCtO :: HasDebugCallStack => CtOrigin -> SDoc
pprCtO (OccurrenceOf name) = hsep [text "a use of", quotes (ppr name)]
@@ -945,7 +1033,7 @@ pprCtO (ScOrigin (IsQC {}) _) = text "the head of a quantified constraint"
pprCtO DerivClauseOrigin = text "the 'deriving' clause of a data type declaration"
pprCtO StandAloneDerivOrigin = text "a 'deriving' declaration"
pprCtO DefaultOrigin = text "a 'default' declaration"
-pprCtO DoStmtOrigin = text "a do statement"
+pprCtO DoStmtOrigin = text "a do statement"
pprCtO MCompOrigin = text "a statement in a monad comprehension"
pprCtO ProcOrigin = text "a proc expression"
pprCtO ArrowCmdOrigin = text "an arrow command"
@@ -990,7 +1078,13 @@ pprCtO (ImpedanceMatching {}) = text "combining required constraints"
pprCtO (NonLinearPatternOrigin _ pat) = hsep [text "a non-linear pattern" <+> quotes (ppr pat)]
pprCtO (ExpansionOrigin (OrigPat p)) = hsep [text "a pattern" <+> quotes (ppr p)]
pprCtO (ExpansionOrigin (OrigStmt{})) = text "a do statement"
-pprCtO (ExpansionOrigin (OrigExpr{})) = text "an expression"
+pprCtO (ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ f)))) = hsep [text "selecting the field", quotes (ppr f)]
+pprCtO (ExpansionOrigin (OrigExpr e)) = text "an expression" <+> ppr e
+pprCtO (ExpectedFunTySyntaxOp{}) = text "a rebindable syntax operator"
+pprCtO (ExpectedFunTyViewPat{}) = text "a view pattern"
+pprCtO (ExpectedFunTyArg{}) = text "a funtion head"
+pprCtO (ExpectedFunTyMatches{}) = text "a match statement"
+pprCtO (ExpectedFunTyLam{}) = text "a lambda expression"
pprNonLinearPatternReason :: HasDebugCallStack => NonLinearPatternReason -> SDoc
@@ -1204,7 +1298,7 @@ data FixedRuntimeRepContext
--
-- See 'ExpectedFunTyOrigin' for more details.
| FRRExpectedFunTy
- !ExpectedFunTyOrigin
+ !CtOrigin -- !ExpectedFunTyOrigin
!Int
-- ^ argument position (1-indexed)
@@ -1285,8 +1379,8 @@ pprFixedRuntimeRepContext FRRBindStmtGuard
= sep [ text "The body of the bind statement" ]
pprFixedRuntimeRepContext (FRRArrow arrowContext)
= pprFRRArrowContext arrowContext
-pprFixedRuntimeRepContext (FRRExpectedFunTy funTyOrig arg_pos)
- = pprExpectedFunTyOrigin funTyOrig arg_pos
+pprFixedRuntimeRepContext (FRRExpectedFunTy funTyOrig _)
+ = pprCtOrigin funTyOrig
instance Outputable FixedRuntimeRepContext where
ppr = pprFixedRuntimeRepContext
@@ -1439,102 +1533,24 @@ instance Outputable FRRArrowContext where
-- Uses 'pprExpectedFunTyOrigin'.
-- See 'FixedRuntimeRepContext' for the situations in which
-- representation-polymorphism checks are performed.
-data ExpectedFunTyOrigin
-
- -- | A rebindable syntax operator is expected to have a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyDoBind, RepPolyDoBody{1,2}, RepPolyMc{Bind,Body,Guard}, RepPolyNPlusK
- = forall (p :: Pass)
- . (OutputableBndrId p)
- => ExpectedFunTySyntaxOp !CtOrigin !(HsExpr (GhcPass p))
- -- ^ rebindable syntax operator
-
- -- | A view pattern must have a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyBinder
- | ExpectedFunTyViewPat
- !(HsExpr GhcRn)
- -- ^ function used in the view pattern
-
- -- | Need to be able to extract an argument type from a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyApp
- | forall (p :: Pass)
- . Outputable (HsExpr (GhcPass p)) => ExpectedFunTyArg
- !TypedThing
- -- ^ function
- !(HsExpr (GhcPass p))
- -- ^ argument
-
- -- | Ensure that a function defined by equations indeed has a function type
- -- with the appropriate number of arguments.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyBinder, RepPolyRecordPattern, RepPolyWildcardPattern
- | ExpectedFunTyMatches
- !TypedThing
- -- ^ name of the function
- !(MatchGroup GhcRn (LHsExpr GhcRn))
- -- ^ equations
-
- -- | Ensure that a lambda abstraction has a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyLambda, RepPolyMatch
- | ExpectedFunTyLam HsLamVariant
- !(HsExpr GhcRn)
- -- ^ the entire lambda-case expression
-
-pprExpectedFunTyOrigin :: ExpectedFunTyOrigin
- -> Int -- ^ argument position (starting at 1)
- -> SDoc
-pprExpectedFunTyOrigin funTy_origin i =
- case funTy_origin of
- ExpectedFunTySyntaxOp orig op ->
- vcat [ sep [ the_arg_of
- , text "the rebindable syntax operator"
- , quotes (ppr op) ]
- , nest 2 (ppr orig) ]
- ExpectedFunTyViewPat expr ->
- vcat [ the_arg_of <+> text "the view pattern"
- , nest 2 (ppr expr) ]
- ExpectedFunTyArg fun arg ->
- sep [ text "The argument"
- , quotes (ppr arg)
- , text "of"
- , quotes (ppr fun) ]
- ExpectedFunTyMatches fun (MG { mg_alts = L _ alts })
- | null alts
- -> the_arg_of <+> quotes (ppr fun)
- | otherwise
- -> text "The" <+> speakNth i <+> text "pattern in the equation" <> plural alts
- <+> text "for" <+> quotes (ppr fun)
- ExpectedFunTyLam lam_variant _ -> binder_of $ lamCaseKeyword lam_variant
- where
- the_arg_of :: SDoc
- the_arg_of = text "The" <+> speakNth i <+> text "argument of"
- binder_of :: SDoc -> SDoc
- binder_of what = text "The binder of the" <+> what <+> text "expression"
-pprExpectedFunTyHerald :: ExpectedFunTyOrigin -> SDoc
+pprExpectedFunTyHerald :: CtOrigin -> SDoc
pprExpectedFunTyHerald (ExpectedFunTySyntaxOp {})
= text "This rebindable syntax expects a function with"
pprExpectedFunTyHerald (ExpectedFunTyViewPat {})
= text "A view pattern expression expects"
-pprExpectedFunTyHerald (ExpectedFunTyArg fun _)
+pprExpectedFunTyHerald (ExpectedFunTyArg _ fun _)
= sep [ text "The function" <+> quotes (ppr fun)
, text "is applied to" ]
-pprExpectedFunTyHerald (ExpectedFunTyMatches fun (MG { mg_alts = L _ alts }))
+pprExpectedFunTyHerald (ExpectedFunTyMatches _ fun (MG { mg_alts = L _ alts }))
= text "The equation" <> plural alts <+> text "for" <+> quotes (ppr fun) <+> hasOrHave alts
pprExpectedFunTyHerald (ExpectedFunTyLam lam_variant expr)
= sep [ text "The" <+> lamCaseKeyword lam_variant <+> text "expression"
<+> quotes (pprSetDepth (PartWay 1) (ppr expr))
-- The pprSetDepth makes the lambda abstraction print briefly
, text "has" ]
+pprExpectedFunTyHerald orig = ppr (Shouldn'tHappenOrigin "pprExpectedFunTyHerald") <+> ppr orig
{- *******************************************************************
* *
=====================================
compiler/GHC/Tc/Utils/Unify.hs
=====================================
@@ -135,7 +135,7 @@ import Data.Traversable (for)
--
-- See Note [Return arguments with a fixed RuntimeRep].
matchActualFunTy
- :: ExpectedFunTyOrigin
+ :: CtOrigin
-- ^ See Note [Herald for matchExpectedFunTys]
-> Maybe TypedThing
-- ^ The thing with type TcSigmaType
@@ -174,7 +174,7 @@ matchActualFunTy herald mb_thing err_info fun_ty
go (FunTy { ft_af = af, ft_mult = w, ft_arg = arg_ty, ft_res = res_ty })
= assert (isVisibleFunArg af) $
- do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy herald 1) arg_ty
+ do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy (updatePositionCtOrigin 1 herald) 1) arg_ty
; return (idHsWrapper, Scaled w arg_ty, res_ty) }
go ty@(TyVarTy tv)
@@ -241,7 +241,7 @@ Ugh!
-- INVARIANT: the returned argument types all have a syntactically fixed RuntimeRep
-- in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
-- See Note [Return arguments with a fixed RuntimeRep].
-matchActualFunTys :: ExpectedFunTyOrigin -- ^ See Note [Herald for matchExpectedFunTys]
+matchActualFunTys :: CtOrigin -- ^ See Note [Herald for matchExpectedFunTys]
-> CtOrigin
-> Arity
-> TcSigmaType
@@ -776,7 +776,7 @@ Example:
-- in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
-- See Note [Return arguments with a fixed RuntimeRep].
matchExpectedFunTys :: forall a.
- ExpectedFunTyOrigin -- See Note [Herald for matchExpectedFunTys]
+ CtOrigin -- See Note [Herald for matchExpectedFunTys]
-> UserTypeCtxt
-> VisArity
-> ExpSigmaType
@@ -852,7 +852,7 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
, ft_arg = arg_ty, ft_res = res_ty })
= assert (isVisibleFunArg af) $
do { let arg_pos = arity - n_req + 1 -- 1 for the first argument etc
- ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy herald arg_pos) arg_ty
+ ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos) arg_ty
; (wrap_res, result) <- check (n_req - 1)
(mkCheckExpFunPatTy (Scaled mult arg_ty) : rev_pat_tys)
res_ty
@@ -905,19 +905,19 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
; co <- unifyType Nothing (mkScaledFunTys more_arg_tys res_ty) fun_ty
; return (mkWpCastN co, result) }
-new_infer_arg_ty :: ExpectedFunTyOrigin -> Int -> TcM (Scaled ExpSigmaTypeFRR)
+new_infer_arg_ty :: CtOrigin -> Int -> TcM (Scaled ExpSigmaTypeFRR)
new_infer_arg_ty herald arg_pos -- position for error messages only
= do { mult <- newFlexiTyVarTy multiplicityTy
- ; inf_hole <- newInferExpTypeFRR (FRRExpectedFunTy herald arg_pos)
+ ; inf_hole <- newInferExpTypeFRR (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos)
; return (mkScaled mult inf_hole) }
-new_check_arg_ty :: ExpectedFunTyOrigin -> Int -> TcM (Scaled TcType)
+new_check_arg_ty :: CtOrigin -> Int -> TcM (Scaled TcType)
new_check_arg_ty herald arg_pos -- Position for error messages only, 1 for first arg
= do { mult <- newFlexiTyVarTy multiplicityTy
- ; arg_ty <- newOpenFlexiFRRTyVarTy (FRRExpectedFunTy herald arg_pos)
+ ; arg_ty <- newOpenFlexiFRRTyVarTy (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos)
; return (mkScaled mult arg_ty) }
-mkFunTysMsg :: ExpectedFunTyOrigin
+mkFunTysMsg :: CtOrigin
-> (VisArity, TcType)
-> TidyEnv -> ZonkM (TidyEnv, ErrCtxtMsg)
-- See Note [Reporting application arity errors]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb0e46017ed50814e806438c268374a…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb0e46017ed50814e806438c268374a…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/romes/24212] Read Toolchain.Target files rather than 'settings'
by Rodrigo Mesquita (@alt-romes) 14 Jul '25
by Rodrigo Mesquita (@alt-romes) 14 Jul '25
14 Jul '25
Rodrigo Mesquita pushed to branch wip/romes/24212 at Glasgow Haskell Compiler / GHC
Commits:
e60079a0 by Rodrigo Mesquita at 2025-07-14T15:09:04+01:00
Read Toolchain.Target files rather than 'settings'
This commit makes GHC read `lib/targets/default.target`, a file with a
serialized value of `ghc-toolchain`'s `GHC.Toolchain.Target`.
Moreover, it removes all the now-redundant entries from `lib/settings`
that are configured as part of a `Target` but were being written into
`settings`.
This makes it easier to support multiple targets from the same compiler
(aka runtime retargetability). `ghc-toolchain` can be re-run many times
standalone to produce a `Target` description for different targets, and,
in the future, GHC will be able to pick at runtime amongst different
`Target` files.
This commit only makes it read the default `Target` configured in-tree
or configured when installing the bindist.
The remaining bits of `settings` need to be moved to `Target` in follow
up commits, but ultimately they all should be moved since they are
per-target relevant.
Fixes #24212
- - - - -
30 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Settings.hs
- compiler/GHC/Settings/IO.hs
- compiler/GHC/SysTools/BaseDir.hs
- compiler/ghc.cabal.in
- configure.ac
- distrib/configure.ac.in
- hadrian/bindist/Makefile
- hadrian/bindist/config.mk.in
- hadrian/cfg/system.config.in
- hadrian/src/Base.hs
- hadrian/src/Rules/Generate.hs
- libraries/ghc-boot/GHC/Settings/Utils.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
- − m4/fp_settings.m4
- m4/fp_setup_windows_toolchain.m4
- + m4/subst_tooldir.m4
- mk/hsc2hs.in
- testsuite/tests/ghc-api/T20757.hs
- testsuite/tests/ghc-api/settings-escape/T24265.hs
- testsuite/tests/ghc-api/settings-escape/T24265.stderr
- + testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep
- utils/ghc-pkg/Main.hs
- utils/ghc-pkg/ghc-pkg.cabal.in
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
Changes:
=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -145,6 +145,7 @@ import GHC.Foreign (withCString, peekCString)
import qualified Data.Set as Set
import qualified GHC.LanguageExtensions as LangExt
+import GHC.Toolchain.Target (Target)
-- -----------------------------------------------------------------------------
-- DynFlags
@@ -178,6 +179,7 @@ data DynFlags = DynFlags {
toolSettings :: {-# UNPACK #-} !ToolSettings,
platformMisc :: {-# UNPACK #-} !PlatformMisc,
rawSettings :: [(String, String)],
+ rawTarget :: Target,
tmpDir :: TempDir,
llvmOptLevel :: Int, -- ^ LLVM optimisation level
@@ -656,6 +658,7 @@ defaultDynFlags mySettings =
targetPlatform = sTargetPlatform mySettings,
platformMisc = sPlatformMisc mySettings,
rawSettings = sRawSettings mySettings,
+ rawTarget = sRawTarget mySettings,
tmpDir = panic "defaultDynFlags: uninitialized tmpDir",
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -280,6 +280,9 @@ import GHC.Parser.Lexer (mkParserOpts, initParserState, P(..), ParseResult(..))
import GHC.SysTools.BaseDir ( expandToolDir, expandTopDir )
+import GHC.Toolchain
+import GHC.Toolchain.Program
+
import Data.IORef
import Control.Arrow ((&&&))
import Control.Monad
@@ -403,6 +406,7 @@ settings dflags = Settings
, sToolSettings = toolSettings dflags
, sPlatformMisc = platformMisc dflags
, sRawSettings = rawSettings dflags
+ , sRawTarget = rawTarget dflags
}
pgm_L :: DynFlags -> String
@@ -3454,9 +3458,58 @@ compilerInfo dflags
-- Next come the settings, so anything else can be overridden
-- in the settings file (as "lookup" uses the first match for the
-- key)
- : map (fmap $ expandDirectories (topDir dflags) (toolDir dflags))
- (rawSettings dflags)
- ++ [("Project version", projectVersion dflags),
+ : map (fmap expandDirectories)
+ (rawSettings dflags)
+ ++
+ [("C compiler command", queryCmd $ ccProgram . tgtCCompiler),
+ ("C compiler flags", queryFlags $ ccProgram . tgtCCompiler),
+ ("C++ compiler command", queryCmd $ cxxProgram . tgtCxxCompiler),
+ ("C++ compiler flags", queryFlags $ cxxProgram . tgtCxxCompiler),
+ ("C compiler link flags", queryFlags $ ccLinkProgram . tgtCCompilerLink),
+ ("C compiler supports -no-pie", queryBool $ ccLinkSupportsNoPie . tgtCCompilerLink),
+ ("CPP command", queryCmd $ cppProgram . tgtCPreprocessor),
+ ("CPP flags", queryFlags $ cppProgram . tgtCPreprocessor),
+ ("Haskell CPP command", queryCmd $ hsCppProgram . tgtHsCPreprocessor),
+ ("Haskell CPP flags", queryFlags $ hsCppProgram . tgtHsCPreprocessor),
+ ("JavaScript CPP command", queryCmdMaybe jsCppProgram tgtJsCPreprocessor),
+ ("JavaScript CPP flags", queryFlagsMaybe jsCppProgram tgtJsCPreprocessor),
+ ("C-- CPP command", queryCmd $ cmmCppProgram . tgtCmmCPreprocessor),
+ ("C-- CPP flags", queryFlags $ cmmCppProgram . tgtCmmCPreprocessor),
+ ("C-- CPP supports -g0", queryBool $ cmmCppSupportsG0 . tgtCmmCPreprocessor),
+ ("ld supports compact unwind", queryBool $ ccLinkSupportsCompactUnwind . tgtCCompilerLink),
+ ("ld supports filelist", queryBool $ ccLinkSupportsFilelist . tgtCCompilerLink),
+ ("ld supports single module", queryBool $ ccLinkSupportsSingleModule . tgtCCompilerLink),
+ ("ld is GNU ld", queryBool $ ccLinkIsGnu . tgtCCompilerLink),
+ ("Merge objects command", queryCmdMaybe mergeObjsProgram tgtMergeObjs),
+ ("Merge objects flags", queryFlagsMaybe mergeObjsProgram tgtMergeObjs),
+ ("Merge objects supports response files", queryBool $ maybe False mergeObjsSupportsResponseFiles . tgtMergeObjs),
+ ("ar command", queryCmd $ arMkArchive . tgtAr),
+ ("ar flags", queryFlags $ arMkArchive . tgtAr),
+ ("ar supports at file", queryBool $ arSupportsAtFile . tgtAr),
+ ("ar supports -L", queryBool $ arSupportsDashL . tgtAr),
+ ("ranlib command", queryCmdMaybe ranlibProgram tgtRanlib),
+ ("otool command", queryCmdMaybe id tgtOtool),
+ ("install_name_tool command", queryCmdMaybe id tgtInstallNameTool),
+ ("windres command", queryCmd $ fromMaybe (Program "/bin/false" []) . tgtWindres),
+ ("cross compiling", queryBool (not . tgtLocallyExecutable)),
+ ("target platform string", query targetPlatformTriple),
+ ("target os", query (show . archOS_OS . tgtArchOs)),
+ ("target arch", query (show . archOS_arch . tgtArchOs)),
+ ("target word size", query $ show . wordSize2Bytes . tgtWordSize),
+ ("target word big endian", queryBool $ (\case BigEndian -> True; LittleEndian -> False) . tgtEndianness),
+ ("target has GNU nonexec stack", queryBool tgtSupportsGnuNonexecStack),
+ ("target has .ident directive", queryBool tgtSupportsIdentDirective),
+ ("target has subsections via symbols", queryBool tgtSupportsSubsectionsViaSymbols),
+ ("Unregisterised", queryBool tgtUnregisterised),
+ ("LLVM target", query tgtLlvmTarget),
+ ("LLVM llc command", queryCmdMaybe id tgtLlc),
+ ("LLVM opt command", queryCmdMaybe id tgtOpt),
+ ("LLVM llvm-as command", queryCmdMaybe id tgtLlvmAs),
+ ("LLVM llvm-as flags", queryFlagsMaybe id tgtLlvmAs),
+ ("Tables next to code", queryBool tgtTablesNextToCode),
+ ("Leading underscore", queryBool tgtSymbolsHaveLeadingUnderscore)
+ ] ++
+ [("Project version", projectVersion dflags),
("Project Git commit id", cProjectGitCommitId),
("Project Version Int", cProjectVersionInt),
("Project Patch Level", cProjectPatchLevel),
@@ -3513,9 +3566,16 @@ compilerInfo dflags
showBool False = "NO"
platform = targetPlatform dflags
isWindows = platformOS platform == OSMinGW32
- useInplaceMinGW = toolSettings_useInplaceMinGW $ toolSettings dflags
- expandDirectories :: FilePath -> Maybe FilePath -> String -> String
- expandDirectories topd mtoold = expandToolDir useInplaceMinGW mtoold . expandTopDir topd
+ expandDirectories = expandToolDir (toolDir dflags) . expandTopDir (topDir dflags)
+ query :: (Target -> a) -> a
+ query f = f (rawTarget dflags)
+ queryFlags f = query (unwords . map escapeArg . prgFlags . f)
+ queryCmd f = expandDirectories (query (prgPath . f))
+ queryBool = showBool . query
+
+ queryCmdMaybe, queryFlagsMaybe :: (a -> Program) -> (Target -> Maybe a) -> String
+ queryCmdMaybe p f = expandDirectories (query (maybe "" (prgPath . p) . f))
+ queryFlagsMaybe p f = query (maybe "" (unwords . map escapeArg . prgFlags . p) . f)
-- Note [Special unit-ids]
-- ~~~~~~~~~~~~~~~~~~~~~~~
@@ -3843,3 +3903,19 @@ updatePlatformConstants dflags mconstants = do
let platform1 = (targetPlatform dflags) { platform_constants = mconstants }
let dflags1 = dflags { targetPlatform = platform1 }
return dflags1
+
+-- ----------------------------------------------------------------------------
+-- Escape Args helpers
+-- ----------------------------------------------------------------------------
+
+-- | Just like 'GHC.ResponseFile.escapeArg', but it is not exposed from base.
+escapeArg :: String -> String
+escapeArg = reverse . foldl' escape []
+
+escape :: String -> Char -> String
+escape cs c
+ | isSpace c
+ || '\\' == c
+ || '\'' == c
+ || '"' == c = c:'\\':cs -- n.b., our caller must reverse the result
+ | otherwise = c:cs
=====================================
compiler/GHC/Settings.hs
=====================================
@@ -23,7 +23,6 @@ module GHC.Settings
, sMergeObjsSupportsResponseFiles
, sLdIsGnuLd
, sGccSupportsNoPie
- , sUseInplaceMinGW
, sArSupportsDashL
, sPgm_L
, sPgm_P
@@ -75,6 +74,7 @@ import GHC.Utils.CliOption
import GHC.Utils.Fingerprint
import GHC.Platform
import GHC.Unit.Types
+import GHC.Toolchain.Target
data Settings = Settings
{ sGhcNameVersion :: {-# UNPACk #-} !GhcNameVersion
@@ -87,6 +87,10 @@ data Settings = Settings
-- You shouldn't need to look things up in rawSettings directly.
-- They should have their own fields instead.
, sRawSettings :: [(String, String)]
+
+ -- Store the target to print out information about the raw target description
+ -- (e.g. in --info)
+ , sRawTarget :: Target
}
data UnitSettings = UnitSettings { unitSettings_baseUnitId :: !UnitId }
@@ -102,7 +106,6 @@ data ToolSettings = ToolSettings
, toolSettings_mergeObjsSupportsResponseFiles :: Bool
, toolSettings_ldIsGnuLd :: Bool
, toolSettings_ccSupportsNoPie :: Bool
- , toolSettings_useInplaceMinGW :: Bool
, toolSettings_arSupportsDashL :: Bool
, toolSettings_cmmCppSupportsG0 :: Bool
@@ -221,8 +224,6 @@ sLdIsGnuLd :: Settings -> Bool
sLdIsGnuLd = toolSettings_ldIsGnuLd . sToolSettings
sGccSupportsNoPie :: Settings -> Bool
sGccSupportsNoPie = toolSettings_ccSupportsNoPie . sToolSettings
-sUseInplaceMinGW :: Settings -> Bool
-sUseInplaceMinGW = toolSettings_useInplaceMinGW . sToolSettings
sArSupportsDashL :: Settings -> Bool
sArSupportsDashL = toolSettings_arSupportsDashL . sToolSettings
=====================================
compiler/GHC/Settings/IO.hs
=====================================
@@ -1,4 +1,4 @@
-
+{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -16,18 +16,20 @@ import GHC.Utils.CliOption
import GHC.Utils.Fingerprint
import GHC.Platform
import GHC.Utils.Panic
-import GHC.ResponseFile
import GHC.Settings
import GHC.SysTools.BaseDir
import GHC.Unit.Types
import Control.Monad.Trans.Except
import Control.Monad.IO.Class
-import Data.Char
import qualified Data.Map as Map
import System.FilePath
import System.Directory
+import GHC.Toolchain.Program
+import GHC.Toolchain
+import GHC.Data.Maybe
+import Data.Bifunctor (Bifunctor(second))
data SettingsError
= SettingsError_MissingData String
@@ -44,6 +46,7 @@ initSettings top_dir = do
libexec :: FilePath -> FilePath
libexec file = top_dir </> ".." </> "bin" </> file
settingsFile = installed "settings"
+ targetFile = installed $ "targets" </> "default.target"
readFileSafe :: FilePath -> ExceptT SettingsError m String
readFileSafe path = liftIO (doesFileExist path) >>= \case
@@ -55,85 +58,72 @@ initSettings top_dir = do
Just s -> pure s
Nothing -> throwE $ SettingsError_BadData $
"Can't parse " ++ show settingsFile
+ targetStr <- readFileSafe targetFile
+ target <- case maybeReadFuzzy @Target targetStr of
+ Just s -> pure s
+ Nothing -> throwE $ SettingsError_BadData $
+ "Can't parse as Target " ++ show targetFile
let mySettings = Map.fromList settingsList
getBooleanSetting :: String -> ExceptT SettingsError m Bool
getBooleanSetting key = either pgmError pure $
getRawBooleanSetting settingsFile mySettings key
- -- On Windows, by mingw is often distributed with GHC,
- -- so we look in TopDir/../mingw/bin,
- -- as well as TopDir/../../mingw/bin for hadrian.
- -- But we might be disabled, in which we we don't do that.
- useInplaceMinGW <- getBooleanSetting "Use inplace MinGW toolchain"
-
-- see Note [topdir: How GHC finds its files]
-- NB: top_dir is assumed to be in standard Unix
-- format, '/' separated
- mtool_dir <- liftIO $ findToolDir useInplaceMinGW top_dir
+ mtool_dir <- liftIO $ findToolDir top_dir
-- see Note [tooldir: How GHC finds mingw on Windows]
- -- Escape 'top_dir' and 'mtool_dir', to make sure we don't accidentally
- -- introduce unescaped spaces. See #24265 and #25204.
- let escaped_top_dir = escapeArg top_dir
- escaped_mtool_dir = fmap escapeArg mtool_dir
-
- getSetting_raw key = either pgmError pure $
+ let getSetting_raw key = either pgmError pure $
getRawSetting settingsFile mySettings key
getSetting_topDir top key = either pgmError pure $
getRawFilePathSetting top settingsFile mySettings key
getSetting_toolDir top tool key =
- expandToolDir useInplaceMinGW tool <$> getSetting_topDir top key
-
- getSetting :: String -> ExceptT SettingsError m String
+ expandToolDir tool <$> getSetting_topDir top key
getSetting key = getSetting_topDir top_dir key
- getToolSetting :: String -> ExceptT SettingsError m String
getToolSetting key = getSetting_toolDir top_dir mtool_dir key
- getFlagsSetting :: String -> ExceptT SettingsError m [String]
- getFlagsSetting key = unescapeArgs <$> getSetting_toolDir escaped_top_dir escaped_mtool_dir key
- -- Make sure to unescape, as we have escaped top_dir and tool_dir.
+
+ expandDirVars top tool = expandToolDir tool . expandTopDir top
+
+ getToolPath :: (Target -> Program) -> String
+ getToolPath key = expandDirVars top_dir mtool_dir (prgPath . key $ target)
+
+ getMaybeToolPath :: (Target -> Maybe Program) -> String
+ getMaybeToolPath key = getToolPath (fromMaybe (Program "" []) . key)
+
+ getToolFlags :: (Target -> Program) -> [String]
+ getToolFlags key = expandDirVars top_dir mtool_dir <$> (prgFlags . key $ target)
+
+ getTool :: (Target -> Program) -> (String, [String])
+ getTool key = (getToolPath key, getToolFlags key)
-- See Note [Settings file] for a little more about this file. We're
-- just partially applying those functions and throwing 'Left's; they're
-- written in a very portable style to keep ghc-boot light.
- targetPlatformString <- getSetting_raw "target platform string"
- cc_prog <- getToolSetting "C compiler command"
- cxx_prog <- getToolSetting "C++ compiler command"
- cc_args0 <- getFlagsSetting "C compiler flags"
- cxx_args <- getFlagsSetting "C++ compiler flags"
- gccSupportsNoPie <- getBooleanSetting "C compiler supports -no-pie"
- cmmCppSupportsG0 <- getBooleanSetting "C-- CPP supports -g0"
- cpp_prog <- getToolSetting "CPP command"
- cpp_args <- map Option <$> getFlagsSetting "CPP flags"
- hs_cpp_prog <- getToolSetting "Haskell CPP command"
- hs_cpp_args <- map Option <$> getFlagsSetting "Haskell CPP flags"
- js_cpp_prog <- getToolSetting "JavaScript CPP command"
- js_cpp_args <- map Option <$> getFlagsSetting "JavaScript CPP flags"
- cmmCpp_prog <- getToolSetting "C-- CPP command"
- cmmCpp_args <- map Option <$> getFlagsSetting "C-- CPP flags"
-
- platform <- either pgmError pure $ getTargetPlatform settingsFile mySettings
-
- let unreg_cc_args = if platformUnregisterised platform
- then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
- else []
- cc_args = cc_args0 ++ unreg_cc_args
-
- -- The extra flags we need to pass gcc when we invoke it to compile .hc code.
- --
- -- -fwrapv is needed for gcc to emit well-behaved code in the presence of
- -- integer wrap around (#952).
- extraGccViaCFlags = if platformUnregisterised platform
- -- configure guarantees cc support these flags
- then ["-fwrapv", "-fno-builtin"]
- else []
-
- ldSupportsCompactUnwind <- getBooleanSetting "ld supports compact unwind"
- ldSupportsFilelist <- getBooleanSetting "ld supports filelist"
- ldSupportsSingleModule <- getBooleanSetting "ld supports single module"
- mergeObjsSupportsResponseFiles <- getBooleanSetting "Merge objects supports response files"
- ldIsGnuLd <- getBooleanSetting "ld is GNU ld"
- arSupportsDashL <- getBooleanSetting "ar supports -L"
-
+ targetHasLibm <- getBooleanSetting "target has libm"
+ let
+ (cc_prog, cc_args0) = getTool (ccProgram . tgtCCompiler)
+ (cxx_prog, cxx_args) = getTool (cxxProgram . tgtCxxCompiler)
+ (cpp_prog, cpp_args) = getTool (cppProgram . tgtCPreprocessor)
+ (hs_cpp_prog, hs_cpp_args) = getTool (hsCppProgram . tgtHsCPreprocessor)
+ (js_cpp_prog, js_cpp_args) = getTool (maybe (Program "" []) jsCppProgram . tgtJsCPreprocessor)
+ (cmmCpp_prog, cmmCpp_args) = getTool (cmmCppProgram . tgtCmmCPreprocessor)
+
+ platform = getTargetPlatform targetHasLibm target
+
+ unreg_cc_args = if platformUnregisterised platform
+ then ["-DNO_REGS", "-DUSE_MINIINTERPRETER"]
+ else []
+ cc_args = cc_args0 ++ unreg_cc_args
+
+ -- The extra flags we need to pass gcc when we invoke it to compile .hc code.
+ --
+ -- -fwrapv is needed for gcc to emit well-behaved code in the presence of
+ -- integer wrap around (#952).
+ extraGccViaCFlags = if platformUnregisterised platform
+ -- configure guarantees cc support these flags
+ then ["-fwrapv", "-fno-builtin"]
+ else []
-- The package database is either a relative path to the location of the settings file
-- OR an absolute path.
@@ -148,41 +138,20 @@ initSettings top_dir = do
-- architecture-specific stuff is done when building Config.hs
unlit_path <- getToolSetting "unlit command"
- windres_path <- getToolSetting "windres command"
- ar_path <- getToolSetting "ar command"
- otool_path <- getToolSetting "otool command"
- install_name_tool_path <- getToolSetting "install_name_tool command"
- ranlib_path <- getToolSetting "ranlib command"
-
- -- HACK, see setPgmP below. We keep 'words' here to remember to fix
- -- Config.hs one day.
-
-
- -- Other things being equal, 'as' and 'ld' are simply 'gcc'
- cc_link_args <- getFlagsSetting "C compiler link flags"
- let as_prog = cc_prog
- as_args = map Option cc_args
- ld_prog = cc_prog
- ld_args = map Option (cc_args ++ cc_link_args)
- ld_r_prog <- getToolSetting "Merge objects command"
- ld_r_args <- getFlagsSetting "Merge objects flags"
- let ld_r
- | null ld_r_prog = Nothing
- | otherwise = Just (ld_r_prog, map Option ld_r_args)
-
- llvmTarget <- getSetting_raw "LLVM target"
-
- -- We just assume on command line
- lc_prog <- getToolSetting "LLVM llc command"
- lo_prog <- getToolSetting "LLVM opt command"
- las_prog <- getToolSetting "LLVM llvm-as command"
- las_args <- map Option <$> getFlagsSetting "LLVM llvm-as flags"
-
- let iserv_prog = libexec "ghc-iserv"
+ -- Other things being equal, 'as' is simply 'gcc'
+ let (cc_link, cc_link_args) = getTool (ccLinkProgram . tgtCCompilerLink)
+ as_prog = cc_prog
+ as_args = map Option cc_args
+ ld_prog = cc_link
+ ld_args = map Option (cc_args ++ cc_link_args)
+ ld_r = do
+ ld_r_prog <- tgtMergeObjs target
+ let (ld_r_path, ld_r_args) = getTool (mergeObjsProgram . const ld_r_prog)
+ pure (ld_r_path, map Option ld_r_args)
+ iserv_prog = libexec "ghc-iserv"
targetRTSLinkerOnlySupportsSharedLibs <- getBooleanSetting "target RTS linker only supports shared libraries"
ghcWithInterpreter <- getBooleanSetting "Use interpreter"
- useLibFFI <- getBooleanSetting "Use LibFFI"
baseUnitId <- getSetting_raw "base unit-id"
@@ -206,36 +175,38 @@ initSettings top_dir = do
}
, sToolSettings = ToolSettings
- { toolSettings_ldSupportsCompactUnwind = ldSupportsCompactUnwind
- , toolSettings_ldSupportsFilelist = ldSupportsFilelist
- , toolSettings_ldSupportsSingleModule = ldSupportsSingleModule
- , toolSettings_mergeObjsSupportsResponseFiles = mergeObjsSupportsResponseFiles
- , toolSettings_ldIsGnuLd = ldIsGnuLd
- , toolSettings_ccSupportsNoPie = gccSupportsNoPie
- , toolSettings_useInplaceMinGW = useInplaceMinGW
- , toolSettings_arSupportsDashL = arSupportsDashL
- , toolSettings_cmmCppSupportsG0 = cmmCppSupportsG0
-
- , toolSettings_pgm_L = unlit_path
- , toolSettings_pgm_P = (hs_cpp_prog, hs_cpp_args)
- , toolSettings_pgm_JSP = (js_cpp_prog, js_cpp_args)
- , toolSettings_pgm_CmmP = (cmmCpp_prog, cmmCpp_args)
- , toolSettings_pgm_F = ""
- , toolSettings_pgm_c = cc_prog
- , toolSettings_pgm_cxx = cxx_prog
- , toolSettings_pgm_cpp = (cpp_prog, cpp_args)
- , toolSettings_pgm_a = (as_prog, as_args)
- , toolSettings_pgm_l = (ld_prog, ld_args)
- , toolSettings_pgm_lm = ld_r
- , toolSettings_pgm_windres = windres_path
- , toolSettings_pgm_ar = ar_path
- , toolSettings_pgm_otool = otool_path
- , toolSettings_pgm_install_name_tool = install_name_tool_path
- , toolSettings_pgm_ranlib = ranlib_path
- , toolSettings_pgm_lo = (lo_prog,[])
- , toolSettings_pgm_lc = (lc_prog,[])
- , toolSettings_pgm_las = (las_prog, las_args)
- , toolSettings_pgm_i = iserv_prog
+ { toolSettings_ldSupportsCompactUnwind = ccLinkSupportsCompactUnwind $ tgtCCompilerLink target
+ , toolSettings_ldSupportsFilelist = ccLinkSupportsFilelist $ tgtCCompilerLink target
+ , toolSettings_ldSupportsSingleModule = ccLinkSupportsSingleModule $ tgtCCompilerLink target
+ , toolSettings_ldIsGnuLd = ccLinkIsGnu $ tgtCCompilerLink target
+ , toolSettings_ccSupportsNoPie = ccLinkSupportsNoPie $ tgtCCompilerLink target
+ , toolSettings_mergeObjsSupportsResponseFiles
+ = maybe False mergeObjsSupportsResponseFiles
+ $ tgtMergeObjs target
+ , toolSettings_arSupportsDashL = arSupportsDashL $ tgtAr target
+ , toolSettings_cmmCppSupportsG0 = cmmCppSupportsG0 $ tgtCmmCPreprocessor target
+
+ , toolSettings_pgm_L = unlit_path
+ , toolSettings_pgm_P = (hs_cpp_prog, map Option hs_cpp_args)
+ , toolSettings_pgm_JSP = (js_cpp_prog, map Option js_cpp_args)
+ , toolSettings_pgm_CmmP = (cmmCpp_prog, map Option cmmCpp_args)
+ , toolSettings_pgm_F = ""
+ , toolSettings_pgm_c = cc_prog
+ , toolSettings_pgm_cxx = cxx_prog
+ , toolSettings_pgm_cpp = (cpp_prog, map Option cpp_args)
+ , toolSettings_pgm_a = (as_prog, as_args)
+ , toolSettings_pgm_l = (ld_prog, ld_args)
+ , toolSettings_pgm_lm = ld_r
+ , toolSettings_pgm_windres = getMaybeToolPath tgtWindres
+ , toolSettings_pgm_ar = getToolPath (arMkArchive . tgtAr)
+ , toolSettings_pgm_otool = getMaybeToolPath tgtOtool
+ , toolSettings_pgm_install_name_tool = getMaybeToolPath tgtInstallNameTool
+ , toolSettings_pgm_ranlib = getMaybeToolPath (fmap ranlibProgram . tgtRanlib)
+ , toolSettings_pgm_lo = (getMaybeToolPath tgtOpt,[])
+ , toolSettings_pgm_lc = (getMaybeToolPath tgtLlc,[])
+ , toolSettings_pgm_las = second (map Option) $
+ getTool (fromMaybe (Program "" []) . tgtLlvmAs)
+ , toolSettings_pgm_i = iserv_prog
, toolSettings_opt_L = []
, toolSettings_opt_P = []
, toolSettings_opt_JSP = []
@@ -260,65 +231,30 @@ initSettings top_dir = do
, sTargetPlatform = platform
, sPlatformMisc = PlatformMisc
- { platformMisc_targetPlatformString = targetPlatformString
+ { platformMisc_targetPlatformString = targetPlatformTriple target
, platformMisc_ghcWithInterpreter = ghcWithInterpreter
- , platformMisc_libFFI = useLibFFI
- , platformMisc_llvmTarget = llvmTarget
+ , platformMisc_libFFI = tgtUseLibffiForAdjustors target
+ , platformMisc_llvmTarget = tgtLlvmTarget target
, platformMisc_targetRTSLinkerOnlySupportsSharedLibs = targetRTSLinkerOnlySupportsSharedLibs
}
, sRawSettings = settingsList
+ , sRawTarget = target
}
-getTargetPlatform
- :: FilePath -- ^ Settings filepath (for error messages)
- -> RawSettings -- ^ Raw settings file contents
- -> Either String Platform
-getTargetPlatform settingsFile settings = do
- let
- getBooleanSetting = getRawBooleanSetting settingsFile settings
- readSetting :: (Show a, Read a) => String -> Either String a
- readSetting = readRawSetting settingsFile settings
-
- targetArchOS <- getTargetArchOS settingsFile settings
- targetWordSize <- readSetting "target word size"
- targetWordBigEndian <- getBooleanSetting "target word big endian"
- targetLeadingUnderscore <- getBooleanSetting "Leading underscore"
- targetUnregisterised <- getBooleanSetting "Unregisterised"
- targetHasGnuNonexecStack <- getBooleanSetting "target has GNU nonexec stack"
- targetHasIdentDirective <- getBooleanSetting "target has .ident directive"
- targetHasSubsectionsViaSymbols <- getBooleanSetting "target has subsections via symbols"
- targetHasLibm <- getBooleanSetting "target has libm"
- crossCompiling <- getBooleanSetting "cross compiling"
- tablesNextToCode <- getBooleanSetting "Tables next to code"
-
- pure $ Platform
- { platformArchOS = targetArchOS
- , platformWordSize = targetWordSize
- , platformByteOrder = if targetWordBigEndian then BigEndian else LittleEndian
- , platformUnregisterised = targetUnregisterised
- , platformHasGnuNonexecStack = targetHasGnuNonexecStack
- , platformHasIdentDirective = targetHasIdentDirective
- , platformHasSubsectionsViaSymbols = targetHasSubsectionsViaSymbols
- , platformIsCrossCompiling = crossCompiling
- , platformLeadingUnderscore = targetLeadingUnderscore
- , platformTablesNextToCode = tablesNextToCode
+getTargetPlatform :: Bool {-^ Does target have libm -} -> Target -> Platform
+getTargetPlatform targetHasLibm Target{..} = Platform
+ { platformArchOS = tgtArchOs
+ , platformWordSize = case tgtWordSize of WS4 -> PW4
+ WS8 -> PW8
+ , platformByteOrder = tgtEndianness
+ , platformUnregisterised = tgtUnregisterised
+ , platformHasGnuNonexecStack = tgtSupportsGnuNonexecStack
+ , platformHasIdentDirective = tgtSupportsIdentDirective
+ , platformHasSubsectionsViaSymbols = tgtSupportsSubsectionsViaSymbols
+ , platformIsCrossCompiling = not tgtLocallyExecutable
+ , platformLeadingUnderscore = tgtSymbolsHaveLeadingUnderscore
+ , platformTablesNextToCode = tgtTablesNextToCode
, platformHasLibm = targetHasLibm
, platform_constants = Nothing -- will be filled later when loading (or building) the RTS unit
}
-
--- ----------------------------------------------------------------------------
--- Escape Args helpers
--- ----------------------------------------------------------------------------
-
--- | Just like 'GHC.ResponseFile.escapeArg', but it is not exposed from base.
-escapeArg :: String -> String
-escapeArg = reverse . foldl' escape []
-
-escape :: String -> Char -> String
-escape cs c
- | isSpace c
- || '\\' == c
- || '\'' == c
- || '"' == c = c:'\\':cs -- n.b., our caller must reverse the result
- | otherwise = c:cs
=====================================
compiler/GHC/SysTools/BaseDir.hs
=====================================
@@ -90,13 +90,10 @@ the build system finds and wires through the toolchain information.
3) The next step is to generate the settings file: The file
`cfg/system.config.in` is preprocessed by configure and the output written to
`system.config`. This serves the same purpose as `config.mk` but it rewrites
- the values that were exported. As an example `SettingsCCompilerCommand` is
- rewritten to `settings-c-compiler-command`.
+ the values that were exported.
Next up is `src/Oracles/Settings.hs` which makes from some Haskell ADT to
- the settings `keys` in the `system.config`. As an example,
- `settings-c-compiler-command` is mapped to
- `SettingsFileSetting_CCompilerCommand`.
+ the settings `keys` in the `system.config`.
The last part of this is the `generateSettings` in `src/Rules/Generate.hs`
which produces the desired settings file out of Hadrian. This is the
@@ -122,15 +119,13 @@ play nice with the system compiler instead.
-- | Expand occurrences of the @$tooldir@ interpolation in a string
-- on Windows, leave the string untouched otherwise.
expandToolDir
- :: Bool -- ^ whether we use the ambient mingw toolchain
- -> Maybe FilePath -- ^ tooldir
+ :: Maybe FilePath -- ^ tooldir
-> String -> String
#if defined(mingw32_HOST_OS)
-expandToolDir False (Just tool_dir) s = expandPathVar "tooldir" tool_dir s
-expandToolDir False Nothing _ = panic "Could not determine $tooldir"
-expandToolDir True _ s = s
+expandToolDir (Just tool_dir) s = expandPathVar "tooldir" tool_dir s
+expandToolDir Nothing _ = panic "Could not determine $tooldir"
#else
-expandToolDir _ _ s = s
+expandToolDir _ s = s
#endif
-- | Returns a Unix-format path pointing to TopDir.
@@ -164,13 +159,13 @@ tryFindTopDir Nothing
-- Returns @Nothing@ when not on Windows.
-- When called on Windows, it either throws an error when the
-- tooldir can't be located, or returns @Just tooldirpath@.
--- If the distro toolchain is being used we treat Windows the same as Linux
+-- If the distro toolchain is being used, there will be no variables to
+-- substitute for anyway, so this is a no-op.
findToolDir
- :: Bool -- ^ whether we use the ambient mingw toolchain
- -> FilePath -- ^ topdir
+ :: FilePath -- ^ topdir
-> IO (Maybe FilePath)
#if defined(mingw32_HOST_OS)
-findToolDir False top_dir = go 0 (top_dir </> "..") []
+findToolDir top_dir = go 0 (top_dir </> "..") []
where maxDepth = 3
go :: Int -> FilePath -> [FilePath] -> IO (Maybe FilePath)
go k path tried
@@ -183,7 +178,6 @@ findToolDir False top_dir = go 0 (top_dir </> "..") []
if oneLevel
then return (Just path)
else go (k+1) (path </> "..") tried'
-findToolDir True _ = return Nothing
#else
-findToolDir _ _ = return Nothing
+findToolDir _ = return Nothing
#endif
=====================================
compiler/ghc.cabal.in
=====================================
@@ -131,6 +131,7 @@ Library
semaphore-compat,
stm,
rts,
+ ghc-toolchain,
ghc-boot == @ProjectVersionMunged@,
ghc-heap == @ProjectVersionMunged@,
ghci == @ProjectVersionMunged@
=====================================
configure.ac
=====================================
@@ -132,6 +132,7 @@ AC_ARG_ENABLE(distro-toolchain,
[FP_CAPITALIZE_YES_NO(["$enableval"], [EnableDistroToolchain])],
[EnableDistroToolchain=NO]
)
+AC_SUBST([EnableDistroToolchain])
if test "$EnableDistroToolchain" = "YES"; then
TarballsAutodownload=NO
@@ -752,8 +753,6 @@ FP_PROG_AR_NEEDS_RANLIB
dnl ** Check to see whether ln -s works
AC_PROG_LN_S
-FP_SETTINGS
-
dnl ** Find the path to sed
AC_PATH_PROGS(SedCmd,gsed sed,sed)
=====================================
distrib/configure.ac.in
=====================================
@@ -89,8 +89,9 @@ AC_ARG_ENABLE(distro-toolchain,
[AS_HELP_STRING([--enable-distro-toolchain],
[Do not use bundled Windows toolchain binaries.])],
[FP_CAPITALIZE_YES_NO(["$enableval"], [EnableDistroToolchain])],
- [EnableDistroToolchain=@SettingsUseDistroMINGW@]
+ [EnableDistroToolchain=@EnableDistroToolchain@]
)
+AC_SUBST([EnableDistroToolchain])
if test "$HostOS" = "mingw32" -a "$EnableDistroToolchain" = "NO"; then
FP_SETUP_WINDOWS_TOOLCHAIN([$hardtop/mingw/], [\$\$topdir/../mingw/])
@@ -384,8 +385,6 @@ fi
AC_SUBST(BaseUnitId)
-FP_SETTINGS
-
# We get caught by
# http://savannah.gnu.org/bugs/index.php?1516
# $(eval ...) inside conditionals causes errors
@@ -418,6 +417,34 @@ AC_OUTPUT
VALIDATE_GHC_TOOLCHAIN([default.target],[default.target.ghc-toolchain])
+if test "$EnableDistroToolchain" = "YES"; then
+ # If the user specified --enable-distro-toolchain then we just use the
+ # executable names, not paths. We do this by finding strings of paths to
+ # programs and keeping the basename only:
+ cp default.target default.target.bak
+
+ while IFS= read -r line; do
+ if echo "$line" | grep -q 'prgPath = "'; then
+ path=$(echo "$line" | sed -E 's/.*prgPath = "([[^"]]+)".*/\1/')
+ base=$(basename "$path")
+ echo "$line" | sed "s|$path|$base|"
+ else
+ echo "$line"
+ fi
+ done < default.target.bak > default.target
+ echo "Applied --enable-distro-toolchain basename substitution to default.target:"
+ cat default.target
+fi
+
+if test "$windows" = YES -a "$EnableDistroToolchain" = "NO"; then
+ # Handle the Windows toolchain installed in FP_SETUP_WINDOWS_TOOLCHAIN.
+ # We need to issue a substitution to use $tooldir,
+ # See Note [tooldir: How GHC finds mingw on Windows]
+ SUBST_TOOLDIR([default.target])
+ echo "Applied tooldir substitution to default.target:"
+ cat default.target
+fi
+
rm -Rf acargs acghc-toolchain actmp-ghc-toolchain
echo "****************************************************"
=====================================
hadrian/bindist/Makefile
=====================================
@@ -85,67 +85,22 @@ WrapperBinsDir=${bindir}
# N.B. this is duplicated from includes/ghc.mk.
lib/settings : config.mk
@rm -f $@
- @echo '[("C compiler command", "$(SettingsCCompilerCommand)")' >> $@
- @echo ',("C compiler flags", "$(SettingsCCompilerFlags)")' >> $@
- @echo ',("C++ compiler command", "$(SettingsCxxCompilerCommand)")' >> $@
- @echo ',("C++ compiler flags", "$(SettingsCxxCompilerFlags)")' >> $@
- @echo ',("C compiler link flags", "$(SettingsCCompilerLinkFlags)")' >> $@
- @echo ',("C compiler supports -no-pie", "$(SettingsCCompilerSupportsNoPie)")' >> $@
- @echo ',("CPP command", "$(SettingsCPPCommand)")' >> $@
- @echo ',("CPP flags", "$(SettingsCPPFlags)")' >> $@
- @echo ',("Haskell CPP command", "$(SettingsHaskellCPPCommand)")' >> $@
- @echo ',("Haskell CPP flags", "$(SettingsHaskellCPPFlags)")' >> $@
- @echo ',("JavaScript CPP command", "$(SettingsJavaScriptCPPCommand)")' >> $@
- @echo ',("JavaScript CPP flags", "$(SettingsJavaScriptCPPFlags)")' >> $@
- @echo ',("C-- CPP command", "$(SettingsCmmCPPCommand)")' >> $@
- @echo ',("C-- CPP flags", "$(SettingsCmmCPPFlags)")' >> $@
- @echo ',("C-- CPP supports -g0", "$(SettingsCmmCPPSupportsG0)")' >> $@
- @echo ',("ld supports compact unwind", "$(LdHasNoCompactUnwind)")' >> $@
- @echo ',("ld supports filelist", "$(LdHasFilelist)")' >> $@
- @echo ',("ld supports single module", "$(LdHasSingleModule)")' >> $@
- @echo ',("ld is GNU ld", "$(LdIsGNULd)")' >> $@
- @echo ',("Merge objects command", "$(SettingsMergeObjectsCommand)")' >> $@
- @echo ',("Merge objects flags", "$(SettingsMergeObjectsFlags)")' >> $@
- @echo ',("Merge objects supports response files", "$(MergeObjsSupportsResponseFiles)")' >> $@
- @echo ',("ar command", "$(SettingsArCommand)")' >> $@
- @echo ',("ar flags", "$(ArArgs)")' >> $@
- @echo ',("ar supports at file", "$(ArSupportsAtFile)")' >> $@
- @echo ',("ar supports -L", "$(ArSupportsDashL)")' >> $@
- @echo ',("ranlib command", "$(SettingsRanlibCommand)")' >> $@
- @echo ',("otool command", "$(SettingsOtoolCommand)")' >> $@
- @echo ',("install_name_tool command", "$(SettingsInstallNameToolCommand)")' >> $@
- @echo ',("windres command", "$(SettingsWindresCommand)")' >> $@
+ @echo '[("target has libm", "$(TargetHasLibm)")' >> $@
@echo ',("unlit command", "$$topdir/../bin/$(CrossCompilePrefix)unlit")' >> $@
- @echo ',("cross compiling", "$(CrossCompiling)")' >> $@
- @echo ',("target platform string", "$(TARGETPLATFORM)")' >> $@
- @echo ',("target os", "$(HaskellTargetOs)")' >> $@
- @echo ',("target arch", "$(HaskellTargetArch)")' >> $@
- @echo ',("target word size", "$(TargetWordSize)")' >> $@
- @echo ',("target word big endian", "$(TargetWordBigEndian)")' >> $@
- @echo ',("target has GNU nonexec stack", "$(TargetHasGnuNonexecStack)")' >> $@
- @echo ',("target has .ident directive", "$(TargetHasIdentDirective)")' >> $@
- @echo ',("target has subsections via symbols", "$(TargetHasSubsectionsViaSymbols)")' >> $@
- @echo ',("target has libm", "$(TargetHasLibm)")' >> $@
- @echo ',("Unregisterised", "$(GhcUnregisterised)")' >> $@
- @echo ',("LLVM target", "$(LLVMTarget)")' >> $@
- @echo ',("LLVM llc command", "$(SettingsLlcCommand)")' >> $@
- @echo ',("LLVM opt command", "$(SettingsOptCommand)")' >> $@
- @echo ',("LLVM llvm-as command", "$(SettingsLlvmAsCommand)")' >> $@
- @echo ',("LLVM llvm-as flags", "$(SettingsLlvmAsFlags)")' >> $@
- @echo ',("Use inplace MinGW toolchain", "$(SettingsUseDistroMINGW)")' >> $@
- @echo
@echo ',("target RTS linker only supports shared libraries", "$(TargetRTSLinkerOnlySupportsSharedLibs)")' >> $@
@echo ',("Use interpreter", "$(GhcWithInterpreter)")' >> $@
@echo ',("Support SMP", "$(GhcWithSMP)")' >> $@
@echo ',("RTS ways", "$(GhcRTSWays)")' >> $@
- @echo ',("Tables next to code", "$(TablesNextToCode)")' >> $@
- @echo ',("Leading underscore", "$(LeadingUnderscore)")' >> $@
- @echo ',("Use LibFFI", "$(UseLibffiForAdjustors)")' >> $@
@echo ',("RTS expects libdw", "$(GhcRtsWithLibdw)")' >> $@
@echo ',("Relative Global Package DB", "package.conf.d")' >> $@
@echo ',("base unit-id", "$(BaseUnitId)")' >> $@
@echo "]" >> $@
+lib/targets/default.target : config.mk default.target
+ @rm -f $@
+ @echo "Copying the bindist-configured default.target to lib/targets/default.target"
+ cp default.target $@
+
# We need to install binaries relative to libraries.
BINARIES = $(wildcard ./bin/*)
.PHONY: install_bin_libdir
@@ -167,7 +122,7 @@ install_bin_direct:
$(INSTALL_PROGRAM) ./bin/* "$(DESTDIR)$(WrapperBinsDir)/"
.PHONY: install_lib
-install_lib: lib/settings
+install_lib: lib/settings lib/targets/default.target
@echo "Copying libraries to $(DESTDIR)$(ActualLibsDir)"
$(INSTALL_DIR) "$(DESTDIR)$(ActualLibsDir)"
=====================================
hadrian/bindist/config.mk.in
=====================================
@@ -130,10 +130,7 @@ INSTALL_DIR = $(INSTALL) -m 755 -d
#-----------------------------------------------------------------------------
# Build configuration
-CrossCompiling = @CrossCompiling@
-CrossCompilePrefix = @CrossCompilePrefix@
-GhcUnregisterised = @Unregisterised@
-EnableDistroToolchain = @SettingsUseDistroMINGW@
+EnableDistroToolchain = @EnableDistroToolchain@
BaseUnitId = @BaseUnitId@
# The THREADED_RTS requires `BaseReg` to be in a register and the
@@ -168,68 +165,9 @@ GhcThreaded = $(if $(findstring thr,$(GhcRTSWays)),YES,NO)
# Configuration for libffi
UseSystemLibFFI=@UseSystemLibFFI@
-UseLibffiForAdjustors=@UseLibffiForAdjustors@
# GHC needs arch-specific tweak at least in
# rts/Libdw.c:set_initial_registers()
GhcRtsWithLibdw=$(strip $(if $(filter $(TargetArch_CPP),i386 x86_64 s390x),@UseLibdw@,NO))
-#-----------------------------------------------------------------------------
-# Settings
-
-# We are in the process of moving the settings file from being entirely
-# generated by configure, to generated being by the build system. Many of these
-# might become redundant.
-# See Note [tooldir: How GHC finds mingw on Windows]
-
-LdHasFilelist = @LdHasFilelist@
-MergeObjsSupportsResponseFiles = @MergeObjsSupportsResponseFiles@
-LdHasBuildId = @LdHasBuildId@
-LdHasFilelist = @LdHasFilelist@
-LdIsGNULd = @LdIsGNULd@
-LdHasNoCompactUnwind = @LdHasNoCompactUnwind@
-LdHasSingleModule = @LdHasSingleModule@
-ArArgs = @ArArgs@
-ArSupportsAtFile = @ArSupportsAtFile@
-ArSupportsDashL = @ArSupportsDashL@
-HaskellHostOs = @HaskellHostOs@
-HaskellHostArch = @HaskellHostArch@
-HaskellTargetOs = @HaskellTargetOs@
-HaskellTargetArch = @HaskellTargetArch@
-TargetWordSize = @TargetWordSize@
-TargetWordBigEndian = @TargetWordBigEndian@
-TargetHasGnuNonexecStack = @TargetHasGnuNonexecStack@
-TargetHasIdentDirective = @TargetHasIdentDirective@
-TargetHasSubsectionsViaSymbols = @TargetHasSubsectionsViaSymbols@
TargetHasLibm = @TargetHasLibm@
-TablesNextToCode = @TablesNextToCode@
-LeadingUnderscore = @LeadingUnderscore@
-LlvmTarget = @LlvmTarget@
-
-SettingsCCompilerCommand = @SettingsCCompilerCommand@
-SettingsCxxCompilerCommand = @SettingsCxxCompilerCommand@
-SettingsCPPCommand = @SettingsCPPCommand@
-SettingsCPPFlags = @SettingsCPPFlags@
-SettingsHaskellCPPCommand = @SettingsHaskellCPPCommand@
-SettingsHaskellCPPFlags = @SettingsHaskellCPPFlags@
-SettingsJavaScriptCPPCommand = @SettingsJavaScriptCPPCommand@
-SettingsJavaScriptCPPFlags = @SettingsJavaScriptCPPFlags@
-SettingsCmmCPPCommand = @SettingsCmmCPPCommand@
-SettingsCmmCPPFlags = @SettingsCmmCPPFlags@
-SettingsCmmCPPSupportsG0 = @SettingsCmmCPPSupportsG0@
-SettingsCCompilerFlags = @SettingsCCompilerFlags@
-SettingsCxxCompilerFlags = @SettingsCxxCompilerFlags@
-SettingsCCompilerLinkFlags = @SettingsCCompilerLinkFlags@
-SettingsCCompilerSupportsNoPie = @SettingsCCompilerSupportsNoPie@
-SettingsMergeObjectsCommand = @SettingsMergeObjectsCommand@
-SettingsMergeObjectsFlags = @SettingsMergeObjectsFlags@
-SettingsArCommand = @SettingsArCommand@
-SettingsOtoolCommand = @SettingsOtoolCommand@
-SettingsInstallNameToolCommand = @SettingsInstallNameToolCommand@
-SettingsRanlibCommand = @SettingsRanlibCommand@
-SettingsWindresCommand = @SettingsWindresCommand@
-SettingsLibtoolCommand = @SettingsLibtoolCommand@
-SettingsLlcCommand = @SettingsLlcCommand@
-SettingsOptCommand = @SettingsOptCommand@
-SettingsLlvmAsCommand = @SettingsLlvmAsCommand@
-SettingsUseDistroMINGW = @SettingsUseDistroMINGW@
=====================================
hadrian/cfg/system.config.in
=====================================
@@ -79,7 +79,7 @@ project-git-commit-id = @ProjectGitCommitId@
# generated by configure, to generated being by the build system. Many of these
# might become redundant.
# See Note [tooldir: How GHC finds mingw on Windows]
-settings-use-distro-mingw = @SettingsUseDistroMINGW@
+settings-use-distro-mingw = @EnableDistroToolchain@
target-has-libm = @TargetHasLibm@
=====================================
hadrian/src/Base.hs
=====================================
@@ -151,6 +151,7 @@ ghcLibDeps stage iplace = do
, "llvm-passes"
, "ghc-interp.js"
, "settings"
+ , "targets" -/- "default.target"
, "ghc-usage.txt"
, "ghci-usage.txt"
, "dyld.mjs"
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -10,7 +10,7 @@ import qualified Data.Set as Set
import Base
import qualified Context
import Expression
-import Hadrian.Oracles.TextFile (lookupSystemConfig)
+import Hadrian.Oracles.TextFile (lookupSystemConfig, getTargetTarget)
import Oracles.Flag hiding (arSupportsAtFile, arSupportsDashL)
import Oracles.ModuleFiles
import Oracles.Setting
@@ -24,7 +24,6 @@ import Target
import Utilities
import GHC.Toolchain as Toolchain hiding (HsCpp(HsCpp))
-import GHC.Toolchain.Program
import GHC.Platform.ArchOS
import Settings.Program (ghcWithInterpreter)
@@ -263,6 +262,7 @@ generateRules = do
let prefix = root -/- stageString stage -/- "lib"
go gen file = generate file (semiEmptyTarget (succStage stage)) gen
(prefix -/- "settings") %> \out -> go (generateSettings out) out
+ (prefix -/- "targets" -/- "default.target") %> \out -> go (show <$> expr getTargetTarget) out
where
file <~+ gen = file %> \out -> generate out emptyTarget gen >> makeExecutable out
@@ -425,7 +425,7 @@ bindistRules = do
, interpolateSetting "LlvmMinVersion" LlvmMinVersion
, interpolateVar "LlvmTarget" $ getTarget tgtLlvmTarget
, interpolateSetting "ProjectVersion" ProjectVersion
- , interpolateVar "SettingsUseDistroMINGW" $ lookupSystemConfig "settings-use-distro-mingw"
+ , interpolateVar "EnableDistroToolchain" $ lookupSystemConfig "settings-use-distro-mingw"
, interpolateVar "TablesNextToCode" $ yesNo <$> getTarget tgtTablesNextToCode
, interpolateVar "TargetHasLibm" $ lookupSystemConfig "target-has-libm"
, interpolateVar "TargetPlatform" $ getTarget targetPlatformTriple
@@ -483,62 +483,12 @@ generateSettings settingsFile = do
let rel_pkg_db = makeRelativeNoSysLink (dropFileName settingsFile) package_db_path
settings <- traverse sequence $
- [ ("C compiler command", queryTarget ccPath)
- , ("C compiler flags", queryTarget ccFlags)
- , ("C++ compiler command", queryTarget cxxPath)
- , ("C++ compiler flags", queryTarget cxxFlags)
- , ("C compiler link flags", queryTarget clinkFlags)
- , ("C compiler supports -no-pie", queryTarget linkSupportsNoPie)
- , ("CPP command", queryTarget cppPath)
- , ("CPP flags", queryTarget cppFlags)
- , ("Haskell CPP command", queryTarget hsCppPath)
- , ("Haskell CPP flags", queryTarget hsCppFlags)
- , ("JavaScript CPP command", queryTarget jsCppPath)
- , ("JavaScript CPP flags", queryTarget jsCppFlags)
- , ("C-- CPP command", queryTarget cmmCppPath)
- , ("C-- CPP flags", queryTarget cmmCppFlags)
- , ("C-- CPP supports -g0", queryTarget cmmCppSupportsG0')
- , ("ld supports compact unwind", queryTarget linkSupportsCompactUnwind)
- , ("ld supports filelist", queryTarget linkSupportsFilelist)
- , ("ld supports single module", queryTarget linkSupportsSingleModule)
- , ("ld is GNU ld", queryTarget linkIsGnu)
- , ("Merge objects command", queryTarget mergeObjsPath)
- , ("Merge objects flags", queryTarget mergeObjsFlags)
- , ("Merge objects supports response files", queryTarget mergeObjsSupportsResponseFiles')
- , ("ar command", queryTarget arPath)
- , ("ar flags", queryTarget arFlags)
- , ("ar supports at file", queryTarget arSupportsAtFile')
- , ("ar supports -L", queryTarget arSupportsDashL')
- , ("ranlib command", queryTarget ranlibPath)
- , ("otool command", queryTarget otoolPath)
- , ("install_name_tool command", queryTarget installNameToolPath)
- , ("windres command", queryTarget (maybe "/bin/false" prgPath . tgtWindres)) -- TODO: /bin/false is not available on many distributions by default, but we keep it as it were before the ghc-toolchain patch. Fix-me.
- , ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
- , ("cross compiling", expr $ yesNo <$> flag CrossCompiling)
- , ("target platform string", queryTarget targetPlatformTriple)
- , ("target os", queryTarget (show . archOS_OS . tgtArchOs))
- , ("target arch", queryTarget (show . archOS_arch . tgtArchOs))
- , ("target word size", queryTarget wordSize)
- , ("target word big endian", queryTarget isBigEndian)
- , ("target has GNU nonexec stack", queryTarget (yesNo . Toolchain.tgtSupportsGnuNonexecStack))
- , ("target has .ident directive", queryTarget (yesNo . Toolchain.tgtSupportsIdentDirective))
- , ("target has subsections via symbols", queryTarget (yesNo . Toolchain.tgtSupportsSubsectionsViaSymbols))
+ [ ("unlit command", ("$topdir/../bin/" <>) <$> expr (programName (ctx { Context.package = unlit })))
, ("target has libm", expr $ lookupSystemConfig "target-has-libm")
- , ("Unregisterised", queryTarget (yesNo . tgtUnregisterised))
- , ("LLVM target", queryTarget tgtLlvmTarget)
- , ("LLVM llc command", queryTarget llcPath)
- , ("LLVM opt command", queryTarget optPath)
- , ("LLVM llvm-as command", queryTarget llvmAsPath)
- , ("LLVM llvm-as flags", queryTarget llvmAsFlags)
- , ("Use inplace MinGW toolchain", expr $ lookupSystemConfig "settings-use-distro-mingw")
-
, ("target RTS linker only supports shared libraries", expr $ yesNo <$> targetRTSLinkerOnlySupportsSharedLibs)
, ("Use interpreter", expr $ yesNo <$> ghcWithInterpreter (predStage stage))
, ("Support SMP", expr $ yesNo <$> targetSupportsSMP)
, ("RTS ways", escapeArgs . map show . Set.toList <$> getRtsWays)
- , ("Tables next to code", queryTarget (yesNo . tgtTablesNextToCode))
- , ("Leading underscore", queryTarget (yesNo . tgtSymbolsHaveLeadingUnderscore))
- , ("Use LibFFI", expr $ yesNo <$> useLibffiForAdjustors)
, ("RTS expects libdw", yesNo <$> getFlag UseLibdw)
, ("Relative Global Package DB", pure rel_pkg_db)
, ("base unit-id", pure base_unit_id)
@@ -550,40 +500,6 @@ generateSettings settingsFile = do
("[" ++ showTuple s)
: ((\s' -> "," ++ showTuple s') <$> ss)
++ ["]"]
- where
- ccPath = prgPath . ccProgram . tgtCCompiler
- ccFlags = escapeArgs . prgFlags . ccProgram . tgtCCompiler
- cxxPath = prgPath . cxxProgram . tgtCxxCompiler
- cxxFlags = escapeArgs . prgFlags . cxxProgram . tgtCxxCompiler
- clinkFlags = escapeArgs . prgFlags . ccLinkProgram . tgtCCompilerLink
- linkSupportsNoPie = yesNo . ccLinkSupportsNoPie . tgtCCompilerLink
- cppPath = prgPath . cppProgram . tgtCPreprocessor
- cppFlags = escapeArgs . prgFlags . cppProgram . tgtCPreprocessor
- hsCppPath = prgPath . hsCppProgram . tgtHsCPreprocessor
- hsCppFlags = escapeArgs . prgFlags . hsCppProgram . tgtHsCPreprocessor
- jsCppPath = maybe "" (prgPath . jsCppProgram) . tgtJsCPreprocessor
- jsCppFlags = maybe "" (escapeArgs . prgFlags . jsCppProgram) . tgtJsCPreprocessor
- cmmCppPath = prgPath . cmmCppProgram . tgtCmmCPreprocessor
- cmmCppFlags = escapeArgs . prgFlags . cmmCppProgram . tgtCmmCPreprocessor
- cmmCppSupportsG0' = yesNo . cmmCppSupportsG0 . tgtCmmCPreprocessor
- mergeObjsPath = maybe "" (prgPath . mergeObjsProgram) . tgtMergeObjs
- mergeObjsFlags = maybe "" (escapeArgs . prgFlags . mergeObjsProgram) . tgtMergeObjs
- linkSupportsSingleModule = yesNo . ccLinkSupportsSingleModule . tgtCCompilerLink
- linkSupportsFilelist = yesNo . ccLinkSupportsFilelist . tgtCCompilerLink
- linkSupportsCompactUnwind = yesNo . ccLinkSupportsCompactUnwind . tgtCCompilerLink
- linkIsGnu = yesNo . ccLinkIsGnu . tgtCCompilerLink
- llcPath = maybe "" prgPath . tgtLlc
- optPath = maybe "" prgPath . tgtOpt
- llvmAsPath = maybe "" prgPath . tgtLlvmAs
- llvmAsFlags = escapeArgs . maybe [] prgFlags . tgtLlvmAs
- arPath = prgPath . arMkArchive . tgtAr
- arFlags = escapeArgs . prgFlags . arMkArchive . tgtAr
- arSupportsAtFile' = yesNo . arSupportsAtFile . tgtAr
- arSupportsDashL' = yesNo . arSupportsDashL . tgtAr
- otoolPath = maybe "" prgPath . tgtOtool
- installNameToolPath = maybe "" prgPath . tgtInstallNameTool
- ranlibPath = maybe "" (prgPath . ranlibProgram) . tgtRanlib
- mergeObjsSupportsResponseFiles' = maybe "NO" (yesNo . mergeObjsSupportsResponseFiles) . tgtMergeObjs
isBigEndian, wordSize :: Toolchain.Target -> String
isBigEndian = yesNo . (\case BigEndian -> True; LittleEndian -> False) . tgtEndianness
=====================================
libraries/ghc-boot/GHC/Settings/Utils.hs
=====================================
@@ -10,6 +10,8 @@ import GHC.BaseDir
import GHC.Platform.ArchOS
import System.FilePath
+import GHC.Toolchain.Target
+
maybeRead :: Read a => String -> Maybe a
maybeRead str = case reads str of
[(x, "")] -> Just x
@@ -36,19 +38,17 @@ type RawSettings = Map String String
-- | Read target Arch/OS from the settings
getTargetArchOS
- :: FilePath -- ^ Settings filepath (for error messages)
- -> RawSettings -- ^ Raw settings file contents
- -> Either String ArchOS
-getTargetArchOS settingsFile settings =
- ArchOS <$> readRawSetting settingsFile settings "target arch"
- <*> readRawSetting settingsFile settings "target os"
+ :: Target -- ^ The 'Target' from which to read the 'ArchOS'
+ -> ArchOS
+getTargetArchOS target = tgtArchOs target
getGlobalPackageDb :: FilePath -> RawSettings -> Either String FilePath
getGlobalPackageDb settingsFile settings = do
rel_db <- getRawSetting settingsFile settings "Relative Global Package DB"
return (dropFileName settingsFile </> rel_db)
-
+--------------------------------------------------------------------------------
+-- lib/settings
getRawSetting
:: FilePath -> RawSettings -> String -> Either String String
@@ -70,10 +70,3 @@ getRawBooleanSetting settingsFile settings key = do
"NO" -> Right False
xs -> Left $ "Bad value for " ++ show key ++ ": " ++ show xs
-readRawSetting
- :: (Show a, Read a) => FilePath -> RawSettings -> String -> Either String a
-readRawSetting settingsFile settings key = case Map.lookup key settings of
- Just xs -> case maybeRead xs of
- Just v -> Right v
- Nothing -> Left $ "Failed to read " ++ show key ++ " value " ++ show xs
- Nothing -> Left $ "No entry for " ++ show key ++ " in " ++ show settingsFile
=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -82,7 +82,8 @@ Library
directory >= 1.2 && < 1.4,
filepath >= 1.3 && < 1.6,
deepseq >= 1.4 && < 1.6,
- ghc-platform >= 0.1,
+ ghc-platform >= 0.1,
+ ghc-toolchain >= 0.1
-- reexport modules from ghc-boot-th so that packages
-- don't have to import all of ghc-boot and ghc-boot-th.
=====================================
libraries/ghc-internal/src/GHC/Internal/ResponseFile.hs
=====================================
@@ -20,7 +20,7 @@
module GHC.Internal.ResponseFile (
getArgsWithResponseFiles,
unescapeArgs,
- escapeArgs,
+ escapeArgs, escapeArg,
expandResponse
) where
=====================================
m4/fp_settings.m4 deleted
=====================================
@@ -1,171 +0,0 @@
-dnl Note [How we configure the bundled windows toolchain]
-dnl ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-dnl As per Note [tooldir: How GHC finds mingw on Windows], when using the
-dnl bundled windows toolchain, the GHC settings file must refer to the
-dnl toolchain through a path relative to $tooldir (binary distributions on
-dnl Windows should work without configure, so the paths must be relative to the
-dnl installation). However, hadrian expects the configured toolchain to use
-dnl full paths to the executable.
-dnl
-dnl This is how the bundled windows toolchain is configured, to define the
-dnl toolchain with paths to the executables, while still writing into GHC
-dnl settings the paths relative to $tooldir:
-dnl
-dnl * If using the bundled toolchain, FP_SETUP_WINDOWS_TOOLCHAIN will be invoked
-dnl
-dnl * FP_SETUP_WINDOWS_TOOLCHAIN will set the toolchain variables to paths
-dnl to the bundled toolchain (e.g. CFLAGS=/full/path/to/mingw/bin/gcc)
-dnl
-dnl * Later on, in FP_SETTINGS, we substitute occurrences of the path to the
-dnl mingw tooldir by $tooldir (see SUBST_TOOLDIR).
-dnl The reason is the Settings* variants of toolchain variables are used by the bindist configure to
-dnl create the settings file, which needs the windows bundled toolchain to be relative to $tooldir.
-dnl
-dnl * Finally, hadrian will also substitute the mingw prefix by $tooldir before writing the toolchain to the settings file (see generateSettings)
-dnl
-dnl The ghc-toolchain program isn't concerned with any of these complications:
-dnl it is passed either the full paths to the toolchain executables, or the bundled
-dnl mingw path is set first on $PATH before invoking it. And ghc-toolchain
-dnl will, as always, output target files with full paths to the executables.
-dnl
-dnl Hadrian accounts for this as it does for the toolchain executables
-dnl configured by configure -- in fact, hadrian doesn't need to know whether
-dnl the toolchain description file was generated by configure or by
-dnl ghc-toolchain.
-
-# SUBST_TOOLDIR
-# ----------------------------------
-# $1 - the variable where to search for occurrences of the path to the
-# inplace mingw, and update by substituting said occurrences by
-# the value of $mingw_install_prefix, where the mingw toolchain will be at
-# install time
-#
-# See Note [How we configure the bundled windows toolchain]
-AC_DEFUN([SUBST_TOOLDIR],
-[
- dnl and Note [How we configure the bundled windows toolchain]
- $1=`echo "$$1" | sed 's%'"$mingw_prefix"'%'"$mingw_install_prefix"'%g'`
-])
-
-# FP_SETTINGS
-# ----------------------------------
-# Set the variables used in the settings file
-AC_DEFUN([FP_SETTINGS],
-[
- SettingsUseDistroMINGW="$EnableDistroToolchain"
-
- SettingsCCompilerCommand="$CC"
- SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2"
- SettingsCxxCompilerCommand="$CXX"
- SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2"
- SettingsCPPCommand="$CPPCmd"
- SettingsCPPFlags="$CONF_CPP_OPTS_STAGE2"
- SettingsHaskellCPPCommand="$HaskellCPPCmd"
- SettingsHaskellCPPFlags="$HaskellCPPArgs"
- SettingsJavaScriptCPPCommand="$JavaScriptCPPCmd"
- SettingsJavaScriptCPPFlags="$JavaScriptCPPArgs"
- SettingsCmmCPPCommand="$CmmCPPCmd"
- SettingsCmmCPPFlags="$CmmCPPArgs"
- SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2"
- SettingsArCommand="$ArCmd"
- SettingsRanlibCommand="$RanlibCmd"
- SettingsMergeObjectsCommand="$MergeObjsCmd"
- SettingsMergeObjectsFlags="$MergeObjsArgs"
-
- AS_CASE(
- ["$CmmCPPSupportsG0"],
- [True], [SettingsCmmCPPSupportsG0=YES],
- [False], [SettingsCmmCPPSupportsG0=NO],
- [AC_MSG_ERROR(Unknown CPPSupportsG0 value $CmmCPPSupportsG0)]
- )
-
- if test -z "$WindresCmd"; then
- SettingsWindresCommand="/bin/false"
- else
- SettingsWindresCommand="$WindresCmd"
- fi
-
- # LLVM backend tools
- SettingsLlcCommand="$LlcCmd"
- SettingsOptCommand="$OptCmd"
- SettingsLlvmAsCommand="$LlvmAsCmd"
- SettingsLlvmAsFlags="$LlvmAsFlags"
-
- if test "$EnableDistroToolchain" = "YES"; then
- # If the user specified --enable-distro-toolchain then we just use the
- # executable names, not paths.
- SettingsCCompilerCommand="$(basename $SettingsCCompilerCommand)"
- SettingsHaskellCPPCommand="$(basename $SettingsHaskellCPPCommand)"
- SettingsCmmCPPCommand="$(basename $SettingsCmmCPPCommand)"
- SettingsJavaScriptCPPCommand="$(basename $SettingsJavaScriptCPPCommand)"
- SettingsLdCommand="$(basename $SettingsLdCommand)"
- SettingsMergeObjectsCommand="$(basename $SettingsMergeObjectsCommand)"
- SettingsArCommand="$(basename $SettingsArCommand)"
- SettingsWindresCommand="$(basename $SettingsWindresCommand)"
- SettingsLlcCommand="$(basename $SettingsLlcCommand)"
- SettingsOptCommand="$(basename $SettingsOptCommand)"
- SettingsLlvmAsCommand="$(basename $SettingsLlvmAsCommand)"
- fi
-
- if test "$windows" = YES -a "$EnableDistroToolchain" = "NO"; then
- # Handle the Windows toolchain installed in FP_SETUP_WINDOWS_TOOLCHAIN.
- # We need to issue a substitution to use $tooldir,
- # See Note [tooldir: How GHC finds mingw on Windows]
- SUBST_TOOLDIR([SettingsCCompilerCommand])
- SUBST_TOOLDIR([SettingsCCompilerFlags])
- SUBST_TOOLDIR([SettingsCxxCompilerCommand])
- SUBST_TOOLDIR([SettingsCxxCompilerFlags])
- SUBST_TOOLDIR([SettingsCCompilerLinkFlags])
- SUBST_TOOLDIR([SettingsCPPCommand])
- SUBST_TOOLDIR([SettingsCPPFlags])
- SUBST_TOOLDIR([SettingsHaskellCPPCommand])
- SUBST_TOOLDIR([SettingsHaskellCPPFlags])
- SUBST_TOOLDIR([SettingsCmmCPPCommand])
- SUBST_TOOLDIR([SettingsCmmCPPFlags])
- SUBST_TOOLDIR([SettingsJavaScriptCPPCommand])
- SUBST_TOOLDIR([SettingsJavaScriptCPPFlags])
- SUBST_TOOLDIR([SettingsMergeObjectsCommand])
- SUBST_TOOLDIR([SettingsMergeObjectsFlags])
- SUBST_TOOLDIR([SettingsArCommand])
- SUBST_TOOLDIR([SettingsRanlibCommand])
- SUBST_TOOLDIR([SettingsWindresCommand])
- SUBST_TOOLDIR([SettingsLlcCommand])
- SUBST_TOOLDIR([SettingsOptCommand])
- SUBST_TOOLDIR([SettingsLlvmAsCommand])
- SUBST_TOOLDIR([SettingsLlvmAsFlags])
- fi
-
- # Mac-only tools
- SettingsOtoolCommand="$OtoolCmd"
- SettingsInstallNameToolCommand="$InstallNameToolCmd"
-
- SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE"
-
- AC_SUBST(SettingsCCompilerCommand)
- AC_SUBST(SettingsCxxCompilerCommand)
- AC_SUBST(SettingsCPPCommand)
- AC_SUBST(SettingsCPPFlags)
- AC_SUBST(SettingsHaskellCPPCommand)
- AC_SUBST(SettingsHaskellCPPFlags)
- AC_SUBST(SettingsCmmCPPCommand)
- AC_SUBST(SettingsCmmCPPFlags)
- AC_SUBST(SettingsCmmCPPSupportsG0)
- AC_SUBST(SettingsJavaScriptCPPCommand)
- AC_SUBST(SettingsJavaScriptCPPFlags)
- AC_SUBST(SettingsCCompilerFlags)
- AC_SUBST(SettingsCxxCompilerFlags)
- AC_SUBST(SettingsCCompilerLinkFlags)
- AC_SUBST(SettingsCCompilerSupportsNoPie)
- AC_SUBST(SettingsMergeObjectsCommand)
- AC_SUBST(SettingsMergeObjectsFlags)
- AC_SUBST(SettingsArCommand)
- AC_SUBST(SettingsRanlibCommand)
- AC_SUBST(SettingsOtoolCommand)
- AC_SUBST(SettingsInstallNameToolCommand)
- AC_SUBST(SettingsWindresCommand)
- AC_SUBST(SettingsLlcCommand)
- AC_SUBST(SettingsOptCommand)
- AC_SUBST(SettingsLlvmAsCommand)
- AC_SUBST(SettingsLlvmAsFlags)
- AC_SUBST(SettingsUseDistroMINGW)
-])
=====================================
m4/fp_setup_windows_toolchain.m4
=====================================
@@ -77,6 +77,7 @@ AC_DEFUN([FP_INSTALL_WINDOWS_TOOLCHAIN],[
# $2 the location that the windows toolchain will be installed in relative to the libdir
AC_DEFUN([FP_SETUP_WINDOWS_TOOLCHAIN],[
+ # TODO: UPDATE COMMENT
# N.B. The parameters which get plopped in the `settings` file used by the
# resulting compiler are computed in `FP_SETTINGS`. Specifically, we use
# $$topdir-relative paths instead of fullpaths to the toolchain, by replacing
=====================================
m4/subst_tooldir.m4
=====================================
@@ -0,0 +1,45 @@
+dnl Note [How we configure the bundled windows toolchain]
+dnl ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+dnl As per Note [tooldir: How GHC finds mingw on Windows], when using the
+dnl bundled windows toolchain, the GHC settings file must refer to the
+dnl toolchain through a path relative to $tooldir (binary distributions on
+dnl Windows should work without configure, so the paths must be relative to the
+dnl installation). However, hadrian expects the configured toolchain to use
+dnl full paths to the executable.
+dnl
+dnl This is how the bundled windows toolchain is configured, to define the
+dnl toolchain with paths to the executables, while still writing into GHC
+dnl settings the paths relative to $tooldir:
+dnl
+dnl * If using the bundled toolchain, FP_SETUP_WINDOWS_TOOLCHAIN will be invoked
+dnl
+dnl * FP_SETUP_WINDOWS_TOOLCHAIN will set the toolchain variables to paths
+dnl to the bundled toolchain (e.g. CFLAGS=/full/path/to/mingw/bin/gcc)
+dnl
+dnl * Later on, at the end of distrib/configure.ac, we substitute occurrences of the path to the
+dnl mingw tooldir by $tooldir (see SUBST_TOOLDIR).
+dnl The reason is the Settings* variants of toolchain variables are used by the bindist configure to
+dnl create the settings file, which needs the windows bundled toolchain to be relative to $tooldir.
+dnl
+dnl The ghc-toolchain program isn't concerned with any of these complications:
+dnl it is passed either the full paths to the toolchain executables, or the bundled
+dnl mingw path is set first on $PATH before invoking it. And ghc-toolchain
+dnl will, as always, output target files with full paths to the executables.
+dnl
+dnl Hadrian accounts for this as it does for the toolchain executables
+dnl configured by configure -- in fact, hadrian doesn't need to know whether
+dnl the toolchain description file was generated by configure or by
+dnl ghc-toolchain.
+
+# SUBST_TOOLDIR
+# ----------------------------------
+# $1 - the filepath where to search for occurrences of the path to the
+# inplace mingw, and update by substituting said occurrences by
+# the value of $mingw_install_prefix, where the mingw toolchain will be at
+# install time
+#
+# See Note [How we configure the bundled windows toolchain]
+AC_DEFUN([SUBST_TOOLDIR],
+[
+ sed -i.bkp $1 's%'"$mingw_prefix"'%'"$mingw_install_prefix"'%g'
+])
=====================================
mk/hsc2hs.in
=====================================
@@ -1,6 +1,6 @@
-HSC2HS_C="@SettingsCCompilerFlags@"
+HSC2HS_C="@CONF_CC_OPTS_STAGE2@"
-HSC2HS_L="@SettingsCCompilerLinkFlags@"
+HSC2HS_L="@CONF_GCC_LINKER_OPTS_STAGE2@"
tflag="--template=$libdir/template-hsc.h"
Iflag="-I$includedir/include/"
=====================================
testsuite/tests/ghc-api/T20757.hs
=====================================
@@ -3,4 +3,4 @@ module Main where
import GHC.SysTools.BaseDir
main :: IO ()
-main = findToolDir False "/" >>= print
+main = findToolDir "/" >>= print
=====================================
testsuite/tests/ghc-api/settings-escape/T24265.hs
=====================================
@@ -16,6 +16,13 @@ import System.Environment
import System.IO (hPutStrLn, stderr)
import System.Exit (exitWith, ExitCode(ExitFailure))
+import GHC.Toolchain
+import GHC.Toolchain.Program
+import GHC.Toolchain.Tools.Cc
+import GHC.Toolchain.Tools.Cpp
+import GHC.Toolchain.Tools.Cxx
+import GHC.Toolchain.Lens
+
-- Precondition: this test case must be executed in a directory with a space.
--
-- First we get the current settings file and amend it with extra arguments that we *know*
@@ -30,35 +37,29 @@ main :: IO ()
main = do
libdir:_args <- getArgs
- (rawSettingOpts, originalSettings) <- runGhc (Just libdir) $ do
+ (rawSettingOpts, rawTargetOpts, originalSettings) <- runGhc (Just libdir) $ do
dflags <- hsc_dflags <$> getSession
- pure (rawSettings dflags, settings dflags)
+ pure (rawSettings dflags, rawTarget dflags, settings dflags)
top_dir <- makeAbsolute "./ghc-install-folder/lib with spaces"
- let argsWithSpaces = "\"-some option\" -some\\ other"
- numberOfExtraArgs = length $ unescapeArgs argsWithSpaces
- -- These are all options that can have multiple 'String' or 'Option' values.
- -- We explicitly do not add 'C compiler link flags' here, as 'initSettings'
- -- already adds the options of "C compiler flags" to this config field.
- multipleArguments = Set.fromList
- [ "Haskell CPP flags"
- , "JavaScript CPP flags"
- , "C-- CPP flags"
- , "C compiler flags"
- , "C++ compiler flags"
- , "CPP flags"
- , "Merge objects flags"
+ let argsWithSpaces l = over l (++["-some option", "-some\\ other"])
+ numberOfExtraArgs = 2
+ -- Test it on a handfull of list of flags
+ multipleArguments =
+ [ _tgtHsCpp % _hsCppProg % _prgFlags -- "Haskell CPP flags"
+ , _tgtCC % _ccProgram % _prgFlags -- "C compiler flags"
+ , _tgtCxx % _cxxProgram % _prgFlags -- "C++ compiler flags"
+ , _tgtCpp % _cppProg % _prgFlags -- "CPP flags"
]
- let rawSettingOptsWithExtraArgs =
- map (\(name, args) -> if Set.member name multipleArguments
- then (name, args ++ " " ++ argsWithSpaces)
- else (name, args)) rawSettingOpts
+ targetWithExtraArgs = foldr argsWithSpaces rawTargetOpts multipleArguments
-- write out the modified settings. We try to keep it legible
writeFile (top_dir ++ "/settings") $
- "[" ++ (intercalate "\n," (map show rawSettingOptsWithExtraArgs)) ++ "]"
+ "[" ++ (intercalate "\n," (map show rawSettingOpts)) ++ "]"
+ writeFile (top_dir ++ "/targets/default.target") $
+ show targetWithExtraArgs
settingsm <- runExceptT $ initSettings top_dir
@@ -113,12 +114,6 @@ main = do
-- Setting 'Haskell CPP flags' contains '$topdir' reference.
-- Resolving those while containing spaces, should not introduce more options.
recordSetting "Haskell CPP flags" (map showOpt . snd . toolSettings_pgm_P . sToolSettings)
- -- Setting 'JavaScript CPP flags' contains '$topdir' reference.
- -- Resolving those while containing spaces, should not introduce more options.
- recordSetting "JavaScript CPP flags" (map showOpt . snd . toolSettings_pgm_JSP . sToolSettings)
- -- Setting 'C-- CPP flags' contains '$topdir' reference.
- -- Resolving those while containing spaces, should not introduce more options.
- recordSetting "C-- CPP flags" (map showOpt . snd . toolSettings_pgm_CmmP . sToolSettings)
-- Setting 'C compiler flags' contains strings with spaces.
-- GHC should not split these by word.
recordSetting "C compiler flags" (toolSettings_opt_c . sToolSettings)
@@ -133,10 +128,6 @@ main = do
-- Setting 'CPP flags' contains strings with spaces.
-- GHC should not split these by word.
recordSetting "CPP flags" (map showOpt . snd . toolSettings_pgm_cpp . sToolSettings)
- -- Setting 'Merge objects flags' contains strings with spaces.
- -- GHC should not split these by word.
- -- If 'Nothing', ignore this test, otherwise the same assertion holds as before.
- recordSettingM "Merge objects flags" (fmap (map showOpt . snd) . toolSettings_pgm_lm . sToolSettings)
-- Setting 'C compiler command' contains '$topdir' reference.
-- Spaces in the final filepath should not be escaped.
recordFpSetting "C compiler" (toolSettings_pgm_c . sToolSettings)
=====================================
testsuite/tests/ghc-api/settings-escape/T24265.stderr
=====================================
@@ -1,9 +1,5 @@
=== 'Haskell CPP flags' contains 2 new entries: True
Contains spaces: True
-=== 'JavaScript CPP flags' contains 2 new entries: True
- Contains spaces: True
-=== 'C-- CPP flags' contains 2 new entries: True
- Contains spaces: True
=== 'C compiler flags' contains 2 new entries: True
Contains spaces: True
=== 'C compiler link flags' contains 2 new entries: True
@@ -12,5 +8,4 @@
Contains spaces: True
=== 'CPP flags' contains 2 new entries: True
Contains spaces: True
-=== 'Merge objects flags' contains expected entries: True
=== FilePath 'C compiler' contains escaped spaces: False
=====================================
testsuite/tests/ghc-api/settings-escape/ghc-install-folder/lib with spaces/targets/.gitkeep
=====================================
=====================================
utils/ghc-pkg/Main.hs
=====================================
@@ -96,6 +96,8 @@ import System.Posix hiding (fdToHandle)
import qualified System.Info(os)
#endif
+import GHC.Toolchain.Target
+
-- | Short-circuit 'any' with a \"monadic predicate\".
anyM :: (Monad m) => (a -> m Bool) -> [a] -> m Bool
anyM _ [] = return False
@@ -583,9 +585,20 @@ readFromSettingsFile settingsFile f = do
-- It's excusable to not have a settings file (for now at
-- least) but completely inexcusable to have a malformed one.
Nothing -> Left $ "Can't parse settings file " ++ show settingsFile
- case f settingsFile mySettings of
- Right archOS -> Right archOS
- Left e -> Left e
+ f settingsFile mySettings
+
+readFromTargetFile :: FilePath
+ -> (Target -> b)
+ -> IO (Either String b)
+readFromTargetFile targetFile f = do
+ targetStr <- readFile targetFile
+ pure $ do
+ target <- case maybeReadFuzzy targetStr of
+ Just t -> Right t
+ -- It's excusable to not have a settings file (for now at
+ -- least) but completely inexcusable to have a malformed one.
+ Nothing -> Left $ "Can't parse .target file " ++ show targetFile
+ Right (f target)
getPkgDatabases :: Verbosity
-> GhcPkg.DbOpenMode mode DbModifySelector
@@ -618,6 +631,7 @@ getPkgDatabases verbosity mode use_user use_cache expand_vars my_flags = do
Nothing -> die err_msg
Just dir -> do
-- Look for where it is given in the settings file, if marked there.
+ -- See Note [Settings file] about this file, and why we need GHC to share it with us.
let settingsFile = dir </> "settings"
exists_settings_file <- doesFileExist settingsFile
erel_db <-
@@ -652,16 +666,15 @@ getPkgDatabases verbosity mode use_user use_cache expand_vars my_flags = do
case [ f | FlagUserConfig f <- my_flags ] of
_ | no_user_db -> return Nothing
[] -> do
- -- See Note [Settings file] about this file, and why we need GHC to share it with us.
- let settingsFile = top_dir </> "settings"
- exists_settings_file <- doesFileExist settingsFile
+ let targetFile = top_dir </> "targets" </> "default.target"
+ exists_settings_file <- doesFileExist targetFile
targetArchOS <- case exists_settings_file of
False -> do
- warn $ "WARNING: settings file doesn't exist " ++ show settingsFile
+ warn $ "WARNING: target file doesn't exist " ++ show targetFile
warn "cannot know target platform so guessing target == host (native compiler)."
pure hostPlatformArchOS
True ->
- readFromSettingsFile settingsFile getTargetArchOS >>= \case
+ readFromTargetFile targetFile getTargetArchOS >>= \case
Right v -> pure v
Left e -> die e
=====================================
utils/ghc-pkg/ghc-pkg.cabal.in
=====================================
@@ -29,6 +29,7 @@ Executable ghc-pkg
Cabal-syntax,
binary,
ghc-boot,
+ ghc-toolchain,
bytestring
if !os(windows)
Build-Depends: unix
=====================================
utils/ghc-toolchain/exe/Main.hs
=====================================
@@ -534,4 +534,3 @@ mkTarget opts = do
}
return t
---- ROMES:TODO: fp_settings.m4 in general which I don't think was ported completely (e.g. the basenames and windows llvm-XX and such)
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
=====================================
@@ -7,6 +7,9 @@ module GHC.Toolchain.Target
, WordSize(..), wordSize2Bytes
+ -- ** Lenses
+ , _tgtCC, _tgtCxx, _tgtCpp, _tgtHsCpp
+
-- * Re-exports
, ByteOrder(..)
) where
@@ -137,3 +140,29 @@ instance Show Target where
, ", tgtInstallNameTool = " ++ show tgtInstallNameTool
, "}"
]
+
+--------------------------------------------------------------------------------
+-- Lenses
+--------------------------------------------------------------------------------
+
+_tgtCC :: Lens Target Cc
+_tgtCC = Lens tgtCCompiler (\x o -> o {tgtCCompiler = x})
+
+_tgtCxx :: Lens Target Cxx
+_tgtCxx = Lens tgtCxxCompiler (\x o -> o {tgtCxxCompiler = x})
+
+_tgtCpp :: Lens Target Cpp
+_tgtCpp = Lens tgtCPreprocessor (\x o -> o {tgtCPreprocessor = x})
+
+_tgtHsCpp :: Lens Target HsCpp
+_tgtHsCpp = Lens tgtHsCPreprocessor (\x o -> o {tgtHsCPreprocessor = x})
+
+_tgtJsCpp :: Lens Target (Maybe JsCpp)
+_tgtJsCpp = Lens tgtJsCPreprocessor (\x o -> o {tgtJsCPreprocessor = x})
+
+_tgtCmmCpp :: Lens Target CmmCpp
+_tgtCmmCpp = Lens tgtCmmCPreprocessor (\x o -> o {tgtCmmCPreprocessor = x})
+
+_tgtMergeObjs :: Lens Target (Maybe MergeObjs)
+_tgtMergeObjs = Lens tgtMergeObjs (\x o -> o {tgtMergeObjs = x})
+
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cpp.hs
=====================================
@@ -5,6 +5,9 @@ module GHC.Toolchain.Tools.Cpp
, Cpp(..), findCpp
, JsCpp(..), findJsCpp
, CmmCpp(..), findCmmCpp
+
+ -- * Lenses
+ , _cppProg, _hsCppProg, _jsCppProg, _cmmCppProg
) where
import Control.Monad
@@ -188,3 +191,18 @@ findCpp progOpt cc = checking "for C preprocessor" $ do
let cppProgram = addFlagIfNew "-E" cpp2
return Cpp{cppProgram}
+--------------------------------------------------------------------------------
+-- Lenses
+--------------------------------------------------------------------------------
+
+_cppProg :: Lens Cpp Program
+_cppProg = Lens cppProgram (\x o -> o{cppProgram = x})
+
+_hsCppProg :: Lens HsCpp Program
+_hsCppProg = Lens hsCppProgram (\x o -> o{hsCppProgram = x})
+
+_jsCppProg :: Lens JsCpp Program
+_jsCppProg = Lens jsCppProgram (\x o -> o{jsCppProgram = x})
+
+_cmmCppProg :: Lens CmmCpp Program
+_cmmCppProg = Lens cmmCppProgram (\x o -> o{cmmCppProgram = x})
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cxx.hs
=====================================
@@ -4,7 +4,7 @@ module GHC.Toolchain.Tools.Cxx
( Cxx(..)
, findCxx
-- * Helpful utilities
- , compileCxx
+ , compileCxx, _cxxProgram
) where
import System.FilePath
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e60079a02a6e3dde7ac0fde8d142532…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e60079a02a6e3dde7ac0fde8d142532…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/spj-apporv-Oct24] - kill ExpectedFunTyOrigin and incorporate it into CtOrigin
by Apoorv Ingle (@ani) 14 Jul '25
by Apoorv Ingle (@ani) 14 Jul '25
14 Jul '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
0b0b8999 by Apoorv Ingle at 2025-07-14T08:58:20-05:00
- kill ExpectedFunTyOrigin and incorporate it into CtOrigin
- fix error message suggestions for record fields
- - - - -
9 changed files:
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Unify.hs
Changes:
=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -24,6 +24,10 @@ import GHC.Driver.Config.Diagnostic
import GHC.Rename.Unbound
+import Language.Haskell.Syntax (DotFieldOcc (..))
+import Language.Haskell.Syntax.Basic (FieldLabelString (..))
+import GHC.Hs.Expr (SrcCodeOrigin (..), HsExpr (..))
+
import GHC.Tc.Types
import GHC.Tc.Utils.Monad
import GHC.Tc.Errors.Types
@@ -2349,7 +2353,7 @@ mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped))
isNothing (lookupLocalRdrOcc lcl_env occ_name)
record_field = case orig of
- GetFieldOrigin name -> Just (mkVarOccFS name)
+ ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ name))) -> Just (mkVarOccFS (field_label $ unLoc $ dfoLabel name))
_ -> Nothing
{- Note [Report candidate instances]
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -857,7 +857,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
-- Rule IARG from Fig 4 of the QL paper:
go1 pos acc fun_ty
(EValArg { ea_arg = arg, ea_ctxt = ctxt } : rest_args)
- = do { let herald = ExpectedFunTyArg (HsExprTcThing tc_fun) (unLoc arg)
+ = do { let herald = ExpectedFunTyArg pos (HsExprTcThing tc_fun) (unLoc arg)
; (wrap, arg_ty, res_ty) <-
-- NB: matchActualFunTy does the rep-poly check.
-- For example, suppose we have f :: forall r (a::TYPE r). a -> Int
@@ -876,7 +876,7 @@ tcInstFun do_ql inst_final fun_orig (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
-- Make a fresh nus for each argument in rule IVAR
new_arg_ty (L _ arg) i
= do { arg_nu <- newOpenFlexiFRRTyVarTy $
- FRRExpectedFunTy (ExpectedFunTyArg (HsExprTcThing tc_fun) arg) i
+ FRRExpectedFunTy (ExpectedFunTyArg i (HsExprTcThing tc_fun) arg) i
-- Following matchActualFunTy, we create nu_i :: TYPE kappa_i[conc],
-- thereby ensuring that the arguments have concrete runtime representations
=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -976,7 +976,7 @@ tcSynArgE orig op sigma_ty syn_ty thing_inside
-- fixed RuntimeRep, as needed to call mkWpFun.
; return (result, match_wrapper <.> fun_wrap) }
where
- herald = ExpectedFunTySyntaxOp orig op
+ herald = ExpectedFunTySyntaxOp 1 orig op
go rho_ty (SynType the_ty)
= do { wrap <- tcSubTypePat orig GenSigCtxt the_ty rho_ty
@@ -1005,7 +1005,7 @@ tcSynArgA orig op sigma_ty arg_shapes res_shape thing_inside
thing_inside (arg_results ++ res_results) (map scaledMult arg_tys ++ arg_res_mults)
; return (result, match_wrapper, arg_wrappers, res_wrapper) }
where
- herald = ExpectedFunTySyntaxOp orig op
+ herald = ExpectedFunTySyntaxOp (length arg_shapes) orig op
tc_syn_args_e :: [TcSigmaTypeFRR] -> [SyntaxOpType]
-> ([TcSigmaTypeFRR] -> [Mult] -> TcM a)
=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -655,7 +655,7 @@ tcInferOverLit lit@(OverLit { ol_val = val
; let
thing = NameThing from_name
mb_thing = Just thing
- herald = ExpectedFunTyArg thing (HsLit noExtField hs_lit)
+ herald = ExpectedFunTyArg 1 thing (HsLit noExtField hs_lit)
; (wrap2, sarg_ty, res_ty) <- matchActualFunTy herald mb_thing (1, from_ty) from_ty
; co <- unifyType mb_thing (hsLitType hs_lit) (scaledThing sarg_ty)
=====================================
compiler/GHC/Tc/Gen/Match.hs
=====================================
@@ -118,7 +118,7 @@ tcFunBindMatches ctxt fun_name mult matches invis_pat_tys exp_ty
= assertPpr (funBindPrecondition matches) (pprMatches matches) $
do { -- Check that they all have the same no of arguments
arity <- checkArgCounts matches
-
+ ; let herald = ExpectedFunTyMatches arity (NameThing fun_name) matches
; traceTc "tcFunBindMatches 1" (ppr fun_name $$ ppr mult $$ ppr exp_ty $$ ppr arity)
; (wrap_fun, r)
@@ -138,7 +138,7 @@ tcFunBindMatches ctxt fun_name mult matches invis_pat_tys exp_ty
; return (wrap_fun, r) }
where
mctxt = mkPrefixFunRhs (noLocA fun_name) noAnn
- herald = ExpectedFunTyMatches (NameThing fun_name) matches
+
funBindPrecondition :: MatchGroup GhcRn (LHsExpr GhcRn) -> Bool
funBindPrecondition (MG { mg_alts = L _ alts })
=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -698,7 +698,7 @@ tc_pat pat_ty penv ps_pat thing_inside = case ps_pat of
-- Note [View patterns and polymorphism]
-- Expression must be a function
- ; let herald = ExpectedFunTyViewPat $ unLoc expr
+ ; let herald = ExpectedFunTyViewPat 1 $ unLoc expr
; (expr_wrap1, Scaled _mult inf_arg_ty, inf_res_sigma)
<- matchActualFunTy herald (Just . HsExprRnThing $ unLoc expr) (1,expr_ty) expr_ty
-- See Note [View patterns and polymorphism]
=====================================
compiler/GHC/Tc/Types/ErrCtxt.hs
=====================================
@@ -17,7 +17,7 @@ import GHC.Hs.Extension
import GHC.Parser.Annotation ( LocatedN, SrcSpanAnnA )
import GHC.Tc.Errors.Types.PromotionErr ( TermLevelUseCtxt )
-import GHC.Tc.Types.Origin ( CtOrigin, UserTypeCtxt, ExpectedFunTyOrigin )
+import GHC.Tc.Types.Origin ( CtOrigin, UserTypeCtxt )
import GHC.Tc.Utils.TcType ( TcType, TcTyCon )
import GHC.Tc.Zonk.Monad ( ZonkM )
@@ -120,7 +120,7 @@ data ErrCtxtMsg
-- | In a function application.
| FunAppCtxt !FunAppCtxtFunArg !Int
-- | In a function call.
- | FunTysCtxt !ExpectedFunTyOrigin !Type !Int !Int
+ | FunTysCtxt !CtOrigin !Type !Int !Int
-- | In the result of a function call.
| FunResCtxt !(HsExpr GhcTc) !Int !Type !Type !Int !Int
-- | In the declaration of a type constructor.
=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -21,6 +21,7 @@ module GHC.Tc.Types.Origin (
CtOrigin(..), exprCtOrigin, lexprCtOrigin, matchesCtOrigin, grhssCtOrigin,
srcCodeOriginCtOrigin,
isVisibleOrigin, toInvisibleOrigin,
+ updatePositionCtOrigin,
pprCtOrigin, isGivenOrigin, isWantedWantedFunDepOrigin,
isWantedSuperclassOrigin,
ClsInstOrQC(..), NakedScFlag(..), NonLinearPatternReason(..),
@@ -45,7 +46,7 @@ module GHC.Tc.Types.Origin (
FRRArrowContext(..), pprFRRArrowContext,
-- ** ExpectedFunTy FixedRuntimeRepOrigin
- ExpectedFunTyOrigin(..), pprExpectedFunTyOrigin, pprExpectedFunTyHerald,
+ pprExpectedFunTyHerald,
-- * InstanceWhat
InstanceWhat(..), SafeOverlapping
@@ -653,8 +654,67 @@ data CtOrigin
Type -- the instantiated type of the method
| AmbiguityCheckOrigin UserTypeCtxt
| ImplicitLiftOrigin HsImplicitLiftSplice
+
| ExpansionOrigin SrcCodeOrigin -- This is due to an expansion of the original thing given by SrcCodeOrigin
+ -- | A rebindable syntax operator is expected to have a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyDoBind, RepPolyDoBody{1,2}, RepPolyMc{Bind,Body,Guard}, RepPolyNPlusK
+ | forall (p :: Pass)
+ . (OutputableBndrId p)
+ => ExpectedFunTySyntaxOp Int
+ !CtOrigin !(HsExpr (GhcPass p))
+ -- ^ rebindable syntax operator
+
+ -- | A view pattern must have a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyBinder
+ | ExpectedFunTyViewPat Int
+ !(HsExpr GhcRn)
+ -- ^ function used in the view pattern
+
+ -- | Need to be able to extract an argument type from a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyApp
+ | forall (p :: Pass)
+ . Outputable (HsExpr (GhcPass p)) => ExpectedFunTyArg
+ Int
+ -- ^ Argument number
+ !TypedThing
+ -- ^ function
+ !(HsExpr (GhcPass p))
+ -- ^ argument
+
+ -- | Ensure that a function defined by equations indeed has a function type
+ -- with the appropriate number of arguments.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyBinder, RepPolyRecordPattern, RepPolyWildcardPattern
+ | ExpectedFunTyMatches Int
+ !TypedThing
+ -- ^ name of the function
+ !(MatchGroup GhcRn (LHsExpr GhcRn))
+ -- ^ equations
+
+ -- | Ensure that a lambda abstraction has a function type.
+ --
+ -- Test cases for representation-polymorphism checks:
+ -- RepPolyLambda, RepPolyMatch
+ | ExpectedFunTyLam HsLamVariant
+ !(HsExpr GhcRn)
+ -- ^ the entire lambda-case expression
+
+updatePositionCtOrigin :: Int -> CtOrigin -> CtOrigin
+updatePositionCtOrigin i (ExpectedFunTySyntaxOp _ c e) = ExpectedFunTySyntaxOp i c e
+updatePositionCtOrigin i (ExpectedFunTyViewPat _ e) = ExpectedFunTyViewPat i e
+updatePositionCtOrigin i (ExpectedFunTyArg _ t e) = ExpectedFunTyArg i t e
+updatePositionCtOrigin i (ExpectedFunTyMatches _ t e) = ExpectedFunTyMatches i t e
+updatePositionCtOrigin _ c = c
+
+
data NonLinearPatternReason
= LazyPatternReason
| GeneralisedPatternReason
@@ -727,7 +787,8 @@ lexprCtOrigin (L _ e) = exprCtOrigin e
exprCtOrigin :: HsExpr GhcRn -> CtOrigin
exprCtOrigin (HsVar _ (L _ (WithUserRdr _ name))) = OccurrenceOf name
-exprCtOrigin (HsGetField _ _ (L _ f)) = GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
+exprCtOrigin e@(HsGetField _ _ (L _ _)) = ExpansionOrigin (OrigExpr e)
+ -- GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
exprCtOrigin (HsOverLabel _ l) = OverLabelOrigin l
exprCtOrigin (ExplicitList {}) = ListOrigin
exprCtOrigin (HsIPVar _ ip) = IPOccOrigin ip
@@ -739,7 +800,7 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1
exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op
exprCtOrigin (NegApp _ e _) = lexprCtOrigin e
exprCtOrigin (HsPar _ e) = lexprCtOrigin e
-exprCtOrigin (HsProjection _ p) = GetFieldOrigin ((field_label . unLoc . dfoLabel . NE.head . NE.reverse) p)
+exprCtOrigin e@(HsProjection _ _) = ExpansionOrigin (OrigExpr e)
exprCtOrigin (SectionL _ _ _) = SectionOrigin
exprCtOrigin (SectionR _ _ _) = SectionOrigin
exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple"
@@ -802,7 +863,7 @@ pprCtOrigin (ExpansionOrigin o)
where what :: SDoc
what = case o of
OrigStmt{} -> text "a do statement"
- OrigExpr e -> text "an expression" <+> ppr e
+ OrigExpr e -> pprCtO (exprCtOrigin e)
OrigPat p -> text "a pattern" <+> ppr p
pprCtOrigin (GivenSCOrigin sk d blk)
@@ -917,9 +978,38 @@ pprCtOrigin (NonLinearPatternOrigin reason pat)
= hang (ctoHerald <+> text "a non-linear pattern" <+> quotes (ppr pat))
2 (pprNonLinearPatternReason reason)
+pprCtOrigin (ExpectedFunTySyntaxOp i orig op) =
+ vcat [ sep [ the_arg_of i
+ , text "the rebindable syntax operator"
+ , quotes (ppr op) ]
+ , nest 2 (ppr orig) ]
+pprCtOrigin (ExpectedFunTyViewPat i expr) =
+ vcat [ the_arg_of i <+> text "the view pattern"
+ , nest 2 (ppr expr) ]
+pprCtOrigin (ExpectedFunTyArg i fun arg) =
+ sep [ text "The" <+> speakNth i <+> text "argument"
+ , quotes (ppr arg)
+ , text "of"
+ , quotes (ppr fun) ]
+pprCtOrigin (ExpectedFunTyMatches i fun (MG { mg_alts = L _ alts }))
+ | null alts
+ = the_arg_of i <+> quotes (ppr fun)
+ | otherwise
+ = text "The" <+> speakNth i <+> text "pattern in the equation" <> plural alts
+ <+> text "for" <+> quotes (ppr fun)
+pprCtOrigin (ExpectedFunTyLam lam_variant _) = binder_of $ lamCaseKeyword lam_variant
+
pprCtOrigin simple_origin
= ctoHerald <+> pprCtO simple_origin
+
+the_arg_of :: Int -> SDoc
+the_arg_of i = text "The" <+> speakNth i <+> text "argument of"
+
+binder_of :: SDoc -> SDoc
+binder_of what = text "The binder of the" <+> what <+> text "expression"
+
+
-- | Short one-liners
pprCtO :: HasDebugCallStack => CtOrigin -> SDoc
pprCtO (OccurrenceOf name) = hsep [text "a use of", quotes (ppr name)]
@@ -945,7 +1035,7 @@ pprCtO (ScOrigin (IsQC {}) _) = text "the head of a quantified constraint"
pprCtO DerivClauseOrigin = text "the 'deriving' clause of a data type declaration"
pprCtO StandAloneDerivOrigin = text "a 'deriving' declaration"
pprCtO DefaultOrigin = text "a 'default' declaration"
-pprCtO DoStmtOrigin = text "a do statement"
+pprCtO DoStmtOrigin = text "a do statement"
pprCtO MCompOrigin = text "a statement in a monad comprehension"
pprCtO ProcOrigin = text "a proc expression"
pprCtO ArrowCmdOrigin = text "an arrow command"
@@ -990,7 +1080,13 @@ pprCtO (ImpedanceMatching {}) = text "combining required constraints"
pprCtO (NonLinearPatternOrigin _ pat) = hsep [text "a non-linear pattern" <+> quotes (ppr pat)]
pprCtO (ExpansionOrigin (OrigPat p)) = hsep [text "a pattern" <+> quotes (ppr p)]
pprCtO (ExpansionOrigin (OrigStmt{})) = text "a do statement"
-pprCtO (ExpansionOrigin (OrigExpr{})) = text "an expression"
+pprCtO (ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ f)))) = hsep [text "selecting the field", quotes (ppr f)]
+pprCtO (ExpansionOrigin (OrigExpr e)) = text "an expression" <+> ppr e
+pprCtO (ExpectedFunTySyntaxOp{}) = text "a rebindable syntax operator"
+pprCtO (ExpectedFunTyViewPat{}) = text "a view pattern"
+pprCtO (ExpectedFunTyArg{}) = text "a funtion head"
+pprCtO (ExpectedFunTyMatches{}) = text "a match statement"
+pprCtO (ExpectedFunTyLam{}) = text "a lambda expression"
pprNonLinearPatternReason :: HasDebugCallStack => NonLinearPatternReason -> SDoc
@@ -1204,7 +1300,7 @@ data FixedRuntimeRepContext
--
-- See 'ExpectedFunTyOrigin' for more details.
| FRRExpectedFunTy
- !ExpectedFunTyOrigin
+ !CtOrigin -- !ExpectedFunTyOrigin
!Int
-- ^ argument position (1-indexed)
@@ -1285,8 +1381,8 @@ pprFixedRuntimeRepContext FRRBindStmtGuard
= sep [ text "The body of the bind statement" ]
pprFixedRuntimeRepContext (FRRArrow arrowContext)
= pprFRRArrowContext arrowContext
-pprFixedRuntimeRepContext (FRRExpectedFunTy funTyOrig arg_pos)
- = pprExpectedFunTyOrigin funTyOrig arg_pos
+pprFixedRuntimeRepContext (FRRExpectedFunTy funTyOrig _)
+ = pprCtOrigin funTyOrig
instance Outputable FixedRuntimeRepContext where
ppr = pprFixedRuntimeRepContext
@@ -1439,102 +1535,56 @@ instance Outputable FRRArrowContext where
-- Uses 'pprExpectedFunTyOrigin'.
-- See 'FixedRuntimeRepContext' for the situations in which
-- representation-polymorphism checks are performed.
-data ExpectedFunTyOrigin
-
- -- | A rebindable syntax operator is expected to have a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyDoBind, RepPolyDoBody{1,2}, RepPolyMc{Bind,Body,Guard}, RepPolyNPlusK
- = forall (p :: Pass)
- . (OutputableBndrId p)
- => ExpectedFunTySyntaxOp !CtOrigin !(HsExpr (GhcPass p))
- -- ^ rebindable syntax operator
-
- -- | A view pattern must have a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyBinder
- | ExpectedFunTyViewPat
- !(HsExpr GhcRn)
- -- ^ function used in the view pattern
-
- -- | Need to be able to extract an argument type from a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyApp
- | forall (p :: Pass)
- . Outputable (HsExpr (GhcPass p)) => ExpectedFunTyArg
- !TypedThing
- -- ^ function
- !(HsExpr (GhcPass p))
- -- ^ argument
-
- -- | Ensure that a function defined by equations indeed has a function type
- -- with the appropriate number of arguments.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyBinder, RepPolyRecordPattern, RepPolyWildcardPattern
- | ExpectedFunTyMatches
- !TypedThing
- -- ^ name of the function
- !(MatchGroup GhcRn (LHsExpr GhcRn))
- -- ^ equations
-
- -- | Ensure that a lambda abstraction has a function type.
- --
- -- Test cases for representation-polymorphism checks:
- -- RepPolyLambda, RepPolyMatch
- | ExpectedFunTyLam HsLamVariant
- !(HsExpr GhcRn)
- -- ^ the entire lambda-case expression
-
-pprExpectedFunTyOrigin :: ExpectedFunTyOrigin
- -> Int -- ^ argument position (starting at 1)
- -> SDoc
-pprExpectedFunTyOrigin funTy_origin i =
- case funTy_origin of
- ExpectedFunTySyntaxOp orig op ->
- vcat [ sep [ the_arg_of
- , text "the rebindable syntax operator"
- , quotes (ppr op) ]
- , nest 2 (ppr orig) ]
- ExpectedFunTyViewPat expr ->
- vcat [ the_arg_of <+> text "the view pattern"
- , nest 2 (ppr expr) ]
- ExpectedFunTyArg fun arg ->
- sep [ text "The argument"
- , quotes (ppr arg)
- , text "of"
- , quotes (ppr fun) ]
- ExpectedFunTyMatches fun (MG { mg_alts = L _ alts })
- | null alts
- -> the_arg_of <+> quotes (ppr fun)
- | otherwise
- -> text "The" <+> speakNth i <+> text "pattern in the equation" <> plural alts
- <+> text "for" <+> quotes (ppr fun)
- ExpectedFunTyLam lam_variant _ -> binder_of $ lamCaseKeyword lam_variant
- where
- the_arg_of :: SDoc
- the_arg_of = text "The" <+> speakNth i <+> text "argument of"
- binder_of :: SDoc -> SDoc
- binder_of what = text "The binder of the" <+> what <+> text "expression"
-pprExpectedFunTyHerald :: ExpectedFunTyOrigin -> SDoc
+-- pprExpectedFunTyOrigin :: -- ExpectedFunTyOrigin
+-- -- -> Int -- ^ argument position (starting at 1)
+-- -> SDoc
+-- pprExpectedFunTyOrigin funTy_origin =
+-- case funTy_origin of
+-- ExpectedFunTySyntaxOp i orig op ->
+-- vcat [ sep [ the_arg_of
+-- , text "the rebindable syntax operator"
+-- , quotes (ppr op) ]
+-- , nest 2 (ppr orig) ]
+-- ExpectedFunTyViewPat i expr ->
+-- vcat [ the_arg_of <+> text "the view pattern"
+-- , nest 2 (ppr expr) ]
+-- ExpectedFunTyArg fun arg ->
+-- sep [ text "The argument"
+-- , quotes (ppr arg)
+-- , text "of"
+-- , quotes (ppr fun) ]
+-- ExpectedFunTyMatches i fun (MG { mg_alts = L _ alts })
+-- | null alts
+-- -> the_arg_of <+> quotes (ppr fun)
+-- | otherwise
+-- -> text "The" <+> speakNth i <+> text "pattern in the equation" <> plural alts
+-- <+> text "for" <+> quotes (ppr fun)
+-- ExpectedFunTyLam lam_variant _ -> binder_of $ lamCaseKeyword lam_variant
+-- where
+-- the_arg_of :: Int -> SDoc
+-- the_arg_of i = text "The" <+> speakNth i <+> text "argument of"
+
+-- binder_of :: SDoc -> SDoc
+-- binder_of what = text "The binder of the" <+> what <+> text "expression"
+
+pprExpectedFunTyHerald :: CtOrigin -> SDoc
pprExpectedFunTyHerald (ExpectedFunTySyntaxOp {})
= text "This rebindable syntax expects a function with"
pprExpectedFunTyHerald (ExpectedFunTyViewPat {})
= text "A view pattern expression expects"
-pprExpectedFunTyHerald (ExpectedFunTyArg fun _)
+pprExpectedFunTyHerald (ExpectedFunTyArg _ fun _)
= sep [ text "The function" <+> quotes (ppr fun)
, text "is applied to" ]
-pprExpectedFunTyHerald (ExpectedFunTyMatches fun (MG { mg_alts = L _ alts }))
+pprExpectedFunTyHerald (ExpectedFunTyMatches _ fun (MG { mg_alts = L _ alts }))
= text "The equation" <> plural alts <+> text "for" <+> quotes (ppr fun) <+> hasOrHave alts
pprExpectedFunTyHerald (ExpectedFunTyLam lam_variant expr)
= sep [ text "The" <+> lamCaseKeyword lam_variant <+> text "expression"
<+> quotes (pprSetDepth (PartWay 1) (ppr expr))
-- The pprSetDepth makes the lambda abstraction print briefly
, text "has" ]
+pprExpectedFunTyHerald orig = ppr (Shouldn'tHappenOrigin "pprExpectedFunTyHerald") <+> ppr orig
{- *******************************************************************
* *
=====================================
compiler/GHC/Tc/Utils/Unify.hs
=====================================
@@ -135,7 +135,7 @@ import Data.Traversable (for)
--
-- See Note [Return arguments with a fixed RuntimeRep].
matchActualFunTy
- :: ExpectedFunTyOrigin
+ :: CtOrigin
-- ^ See Note [Herald for matchExpectedFunTys]
-> Maybe TypedThing
-- ^ The thing with type TcSigmaType
@@ -174,7 +174,7 @@ matchActualFunTy herald mb_thing err_info fun_ty
go (FunTy { ft_af = af, ft_mult = w, ft_arg = arg_ty, ft_res = res_ty })
= assert (isVisibleFunArg af) $
- do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy herald 1) arg_ty
+ do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy (updatePositionCtOrigin 1 herald) 1) arg_ty
; return (idHsWrapper, Scaled w arg_ty, res_ty) }
go ty@(TyVarTy tv)
@@ -241,7 +241,7 @@ Ugh!
-- INVARIANT: the returned argument types all have a syntactically fixed RuntimeRep
-- in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
-- See Note [Return arguments with a fixed RuntimeRep].
-matchActualFunTys :: ExpectedFunTyOrigin -- ^ See Note [Herald for matchExpectedFunTys]
+matchActualFunTys :: CtOrigin -- ^ See Note [Herald for matchExpectedFunTys]
-> CtOrigin
-> Arity
-> TcSigmaType
@@ -776,7 +776,7 @@ Example:
-- in the sense of Note [Fixed RuntimeRep] in GHC.Tc.Utils.Concrete.
-- See Note [Return arguments with a fixed RuntimeRep].
matchExpectedFunTys :: forall a.
- ExpectedFunTyOrigin -- See Note [Herald for matchExpectedFunTys]
+ CtOrigin -- See Note [Herald for matchExpectedFunTys]
-> UserTypeCtxt
-> VisArity
-> ExpSigmaType
@@ -852,7 +852,7 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
, ft_arg = arg_ty, ft_res = res_ty })
= assert (isVisibleFunArg af) $
do { let arg_pos = arity - n_req + 1 -- 1 for the first argument etc
- ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy herald arg_pos) arg_ty
+ ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos) arg_ty
; (wrap_res, result) <- check (n_req - 1)
(mkCheckExpFunPatTy (Scaled mult arg_ty) : rev_pat_tys)
res_ty
@@ -905,19 +905,19 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
; co <- unifyType Nothing (mkScaledFunTys more_arg_tys res_ty) fun_ty
; return (mkWpCastN co, result) }
-new_infer_arg_ty :: ExpectedFunTyOrigin -> Int -> TcM (Scaled ExpSigmaTypeFRR)
+new_infer_arg_ty :: CtOrigin -> Int -> TcM (Scaled ExpSigmaTypeFRR)
new_infer_arg_ty herald arg_pos -- position for error messages only
= do { mult <- newFlexiTyVarTy multiplicityTy
- ; inf_hole <- newInferExpTypeFRR (FRRExpectedFunTy herald arg_pos)
+ ; inf_hole <- newInferExpTypeFRR (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos)
; return (mkScaled mult inf_hole) }
-new_check_arg_ty :: ExpectedFunTyOrigin -> Int -> TcM (Scaled TcType)
+new_check_arg_ty :: CtOrigin -> Int -> TcM (Scaled TcType)
new_check_arg_ty herald arg_pos -- Position for error messages only, 1 for first arg
= do { mult <- newFlexiTyVarTy multiplicityTy
- ; arg_ty <- newOpenFlexiFRRTyVarTy (FRRExpectedFunTy herald arg_pos)
+ ; arg_ty <- newOpenFlexiFRRTyVarTy (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos)
; return (mkScaled mult arg_ty) }
-mkFunTysMsg :: ExpectedFunTyOrigin
+mkFunTysMsg :: CtOrigin
-> (VisArity, TcType)
-> TidyEnv -> ZonkM (TidyEnv, ErrCtxtMsg)
-- See Note [Reporting application arity errors]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b0b8999c64e5ff3fe1889ad345a869…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b0b8999c64e5ff3fe1889ad345a869…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/spj-apporv-Oct24] 118 commits: Consider `PromotedDataCon` in `tyConStupidTheta`
by Apoorv Ingle (@ani) 14 Jul '25
by Apoorv Ingle (@ani) 14 Jul '25
14 Jul '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
8d33d048 by Berk Özkütük at 2025-07-07T20:42:20-04:00
Consider `PromotedDataCon` in `tyConStupidTheta`
Haddock checks data declarations for the stupid theta so as not to
pretty-print them as empty contexts. Type data declarations end up as
`PromotedDataCon`s by the time Haddock performs this check, causing a
panic. This commit extends `tyConStupidTheta` so that it returns an
empty list for `PromotedDataCon`s. This decision was guided by the fact
that type data declarations never have data type contexts (see (R1) in
Note [Type data declarations]).
Fixes #25739.
- - - - -
a26243fd by Ryan Hendrickson at 2025-07-07T20:43:07-04:00
haddock: Document instances from other packages
When attaching instances to `Interface`s, it isn't enough just to look
for instances in the list of `Interface`s being processed. We also need
to look in the modules on which they depend, including those outside of
this package.
Fixes #25147.
Fixes #26079.
- - - - -
0fb24420 by Rodrigo Mesquita at 2025-07-07T20:43:49-04:00
hadrian: Fallback logic for internal interpreter
When determining whether to build the internal interpreter, the `make`
build system had a fallback case for platforms not in the list of
explicitly-supported operating systems and architectures.
This fallback says we should try to build the internal interpreter if
building dynamic GHC programs (if the architecture is unknown).
Fixes #24098
- - - - -
fe925bd4 by Ben Gamari at 2025-07-07T20:44:30-04:00
users-guide: Reference Wasm FFI section
- - - - -
5856284b by Ben Gamari at 2025-07-07T20:44:30-04:00
users-guide: Fix too-short heading warning
- - - - -
a48dcdf3 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Reorganise documentation for allocate* functions
Consolodate interface information into the .h file, keeping just
implementation details in the .c file.
Use Notes stlye in the .h file and refer to notes from the .c file.
- - - - -
de5b528c by Duncan Coutts at 2025-07-07T20:45:18-04:00
Introduce common utilities for allocating arrays
The intention is to share code among the several places that do this
already.
- - - - -
b321319d by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Heap.c
The CMM primop can now report heap overflow.
- - - - -
1d557ffb by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in ThreadLabels.c
Replacing a local utility.
- - - - -
e59a1430 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Threads.c
Replacing local open coded version.
- - - - -
482df1c9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Add exitHeapOverflow helper utility
This will be useful with the array alloc functions, since unlike
allocate/allocateMaybeFail, they do not come in two versions. So if it's
not convenient to propagate failure, then one can use this.
- - - - -
4d3ec8f9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
Use new array alloc utils in Weak.c
Also add a cpp macro CCS_SYSTEM_OR_NULL which does what it says. The
benefit of this is that it allows us to referece CCS_SYSTEM even when
we're not in PROFILING mode. That makes abstracting over profiling vs
normal mode a lot easier.
- - - - -
0c4f2fde by Duncan Coutts at 2025-07-07T20:45:18-04:00
Convert the array alloc primops to use the new array alloc utils
- - - - -
a3354ad9 by Duncan Coutts at 2025-07-07T20:45:18-04:00
While we're at it, add one missing 'likely' hint
To a cmm primops that raises an exception, like the others now do.
- - - - -
33b546bd by meooow25 at 2025-07-07T20:46:09-04:00
Keep scanl' strict in the head on rewrite
`scanl'` forces elements to WHNF when the corresponding `(:)`s are
forced. The rewrite rule for `scanl'` missed forcing the first element,
which is fixed here with a `seq`.
- - - - -
8a69196e by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger/rts: Allow toggling step-in per thread
The RTS global flag `rts_stop_next_breakpoint` globally sets the
interpreter to stop at the immediate next breakpoint.
With this commit, single step mode can additionally be set per thread in
the TSO flag (TSO_STOP_NEXT_BREAKPOINT).
Being able to toggle "stop at next breakpoint" per thread is an
important requirement for implementing "stepping out" of a function in a
multi-threaded context.
And, more generally, having a per-thread flag for single-stepping paves the
way for multi-threaded debugging.
That said, when we want to enable "single step" mode for the whole
interpreted program we still want to stop at the immediate next
breakpoint, whichever thread it belongs to.
That's why we also keep the global `rts_stop_next_breakpoint` flag, with
`rts_enableStopNextBreakpointAll` and `rts_disableStopNextBreakpointAll` helpers.
Preparation for #26042
- - - - -
73d3f864 by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
docs: Case continuation BCOs
This commit documents a subtle interaction between frames for case BCOs
and their parents frames. Namely, case continuation BCOs may refer to
(non-local) variables that are part of the parent's frame.
The note expanding a bit on these details is called [Case continuation BCOs]
- - - - -
d7aeddcf by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger: Implement step-out feature
Implements support for stepping-out of a function (aka breaking right after
returning from a function) in the interactive debugger.
It also introduces a GHCi command :stepout to step-out of a function
being debugged in the interpreter. The feature is described as:
Stop at the first breakpoint immediately after returning from the current
function scope.
Known limitations: because a function tail-call does not push a stack
frame, if step-out is used inside of a function that was tail-called,
execution will not be returned to its caller, but rather its caller's
first non-tail caller. On the other hand, it means the debugger
follows the more realistic execution of the program.
In the following example:
.. code-block:: none
f = do
a
b <--- (1) set breakpoint then step in here
c
b = do
...
d <--- (2) step-into this tail call
d = do
...
something <--- (3) step-out here
...
Stepping-out will stop execution at the `c` invokation in `f`, rather than
stopping at `b`.
The key idea is simple: When step-out is enabled, traverse the runtime
stack until a continuation BCO is found -- and enable the breakpoint
heading that BCO explicitly using its tick-index.
The details are specified in `Note [Debugger: Step-out]` in `rts/Interpreter.c`.
Since PUSH_ALTS BCOs (representing case continuations) were never headed
by a breakpoint (unlike the case alternatives they push), we introduced
the BRK_ALTS instruction to allow the debugger to set a case
continuation to stop at the breakpoint heading the alternative that is
taken. This is further described in `Note [Debugger: BRK_ALTS]`.
Fixes #26042
- - - - -
5d9adf51 by Rodrigo Mesquita at 2025-07-08T07:39:47-04:00
debugger: Filter step-out stops by SrcSpan
To implement step-out, the RTS looks for the first continuation frame on
the stack and explicitly enables its entry breakpoint. However, some
continuations will be contained in the function from which step-out was
initiated (trivial example is a case expression).
Similarly to steplocal, we will filter the breakpoints at which the RTS
yields to the debugger based on the SrcSpan. When doing step-out, only
stop if the breakpoint is /not/ contained in the function from which we
initiated it.
This is especially relevant in monadic statements such as IO which is
compiled to a long chain of case expressions.
See Note [Debugger: Filtering step-out stops]
- - - - -
7677adcc by Cheng Shao at 2025-07-08T07:40:29-04:00
compiler: make ModBreaks serializable
- - - - -
14f67c6d by Rodrigo Mesquita at 2025-07-08T07:40:29-04:00
refactor: "Inspecting the session" moved from GHC
Moved utilities for inspecting the session from the GHC module to
GHC.Driver.Session.Inspect
Purely a clean up
- - - - -
9d3f484a by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Pass the HUG to readModBreaks, not HscEnv
A minor cleanup. The associated history and setupBreakpoint functions
are changed accordingly.
- - - - -
b595f713 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Move readModBreaks to GHC.Runtime.Interpreter
With some small docs changes
- - - - -
d223227a by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Move interpreterProfiled to Interp.Types
Moves interpreterProfiled and interpreterDynamic to
GHC.Runtime.Interpreter.Types from GHC.Runtime.Interpreter.
- - - - -
7fdd0a3d by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Don't import GHC in Debugger.Breakpoints
Remove the top-level
import GHC
from GHC.Runtime.Debugger.Breakpoints
This makes the module dependencies more granular and cleans up the
qualified imports from the code.
- - - - -
5e4da31b by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
refactor: Use BreakpointId in Core and Ifaces
- - - - -
741ac3a8 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
stg2bc: Derive BcM via ReaderT StateT
A small refactor that simplifies GHC.StgToByteCode by deriving-via the
Monad instances for BcM. This is done along the lines of previous
similar refactors like 72b54c0760bbf85be1f73c1a364d4701e5720465.
- - - - -
0414fcc9 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
refact: Split InternalModBreaks out of ModBreaks
There are currently two competing ways of referring to a Breakpoint:
1. Using the Tick module + Tick index
2. Using the Info module + Info index
1. The Tick index is allocated during desugaring in `mkModBreaks`. It is
used to refer to a breakpoint associated to a Core Tick. For a given
Tick module, there are N Ticks indexed by Tick index.
2. The Info index is allocated during code generation (in StgToByteCode)
and uniquely identifies the breakpoints at runtime (and is indeed used
to determine which breakpoint was hit at runtime).
Why we need both is described by Note [Breakpoint identifiers].
For every info index we used to keep a `CgBreakInfo`, a datatype containing
information relevant to ByteCode Generation, in `ModBreaks`.
This commit splits out the `IntMap CgBreakInfo` out of `ModBreaks` into
a new datatype `InternalModBreaks`.
- The purpose is to separate the `ModBreaks` datatype, which stores
data associated from tick-level information which is fixed after
desugaring, from the unrelated `IntMap CgBreakInfo` information
accumulated during bytecode generation.
- We move `ModBreaks` to GHC.HsToCore.Breakpoints
The new `InternalModBreaks` simply combines the `IntMap CgBreakInfo`
with `ModBreaks`. After code generation we construct an
`InternalModBreaks` with the `CgBreakInfo`s we accumulated and the
existing `ModBreaks` and store that in the compiled BCO in `bc_breaks`.
- Note that we previously only updated the `modBreaks_breakInfo`
field of `ModBreaks` at this exact location, and then stored the
updated `ModBreaks` in the same `bc_breaks`.
- We put this new datatype in GHC.ByteCode.Breakpoints
The rest of the pipeline for which CgBreakInfo is relevant is
accordingly updated to also use `InternalModBreaks`
- - - - -
2a097955 by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
cleanup: Use BreakpointIds in bytecode gen
Small clean up to use BreakpointId and InternalBreakpointId more
uniformly in bytecode generation rather than using Module + Ix pairs
- - - - -
0515cc2f by Rodrigo Mesquita at 2025-07-08T07:40:30-04:00
ghci: Allocate BreakArrays at link time only
Previously, a BreakArray would be allocated with a slot for every tick
in a module at `mkModBreaks`, in HsToCore. However, this approach has
a few downsides:
- It interleaves interpreter behaviour (allocating arrays for
breakpoints) within the desugarer
- It is inflexible in the sense it is impossible for the bytecode
generator to add "internal" breakpoints that can be triggered at
runtime, because those wouldn't have a source tick. (This is relevant
for our intended implementation plan of step-out in #26042)
- It ties the BreakArray indices to the *tick* indexes, while at runtime
we would rather just have the *info* indexes (currently we have both
because BreakArrays are indexed by the *tick* one).
Paving the way for #26042 and #26064, this commit moves the allocation
of BreakArrays to bytecode-loading time -- akin to what is done for CCS
arrays.
Since a BreakArray is allocated only when bytecode is linked, if a
breakpoint is set (e.g. `:break 10`) before the bytecode is linked,
there will exist no BreakArray to trigger the breakpoint in.
Therefore, the function to allocate break arrays (`allocateBreakArrays`)
is exposed and also used in GHC.Runtime.Eval to allocate a break array
when a breakpoint is set, if it doesn't exist yet (in the linker env).
- - - - -
8016561f by Simon Peyton Jones at 2025-07-08T07:41:13-04:00
Add a test for T26176
- - - - -
454cd682 by Simon Peyton Jones at 2025-07-08T07:41:13-04:00
Add test for #14010
This test started to work in GHC 9.6 and has worked since.
This MR just adds a regression test
- - - - -
ea2c6673 by Teo Camarasu at 2025-07-08T13:24:43-04:00
Implement user-defined allocation limit handlers
Allocation Limits allow killing a thread if they allocate more than a
user-specified limit.
We extend this feature to allow more versatile behaviour.
- We allow not killing the thread if the limit is exceeded.
- We allow setting a custom handler to be called when the limit is exceeded.
User-specified allocation limit handlers run in a fresh thread and are passed
the ThreadId of the thread that exceeded its limit.
We introduce utility functions for getting and setting the allocation
limits of other threads, so that users can reset the limit of a thread
from a handler. Both of these are somewhat coarse-grained as we are
unaware of the allocations in the current nursery chunk.
We provide several examples of usages in testsuite/tests/rts/T22859.hs
Resolves #22859
- - - - -
03e047f9 by Simon Hengel at 2025-07-08T13:25:25-04:00
Fix typo in using.rst
- - - - -
67957854 by Ben Gamari at 2025-07-09T09:44:44-04:00
compiler: Import AnnotationWrapper from ghc-internal
Since `GHC.Desugar` exported from `base` has been deprecated.
- - - - -
813d99d6 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-compact: Eliminate dependency on ghc-prim
- - - - -
0ec952a1 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Eliminate dependency on ghc-prim
- - - - -
480074c3 by Ben Gamari at 2025-07-09T09:44:44-04:00
ghc-heap: Drop redundant import
- - - - -
03455829 by Ben Gamari at 2025-07-09T09:44:45-04:00
ghc-prim: Bump version to 0.13.1
There are no interface changes from 0.13.0 but the implementation now
lives in `ghc-internal`.
- - - - -
d315345a by Ben Gamari at 2025-07-09T09:44:45-04:00
template-haskell: Bump version number to 2.24.0.0
Bumps exceptions submodule.
- - - - -
004c800e by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump GHC version number to 9.14
- - - - -
eb1a3816 by Ben Gamari at 2025-07-09T09:44:45-04:00
Bump parsec to 3.1.18.0
Bumps parsec submodule.
- - - - -
86f83296 by Ben Gamari at 2025-07-09T09:44:45-04:00
unix: Bump to 2.8.7.0
Bumps unix submodule.
- - - - -
89e13998 by Ben Gamari at 2025-07-09T09:44:45-04:00
binary: Bump to 0.8.9.3
Bumps binary submodule.
- - - - -
55fff191 by Ben Gamari at 2025-07-09T09:44:45-04:00
Win32: Bump to 2.14.2.0
Bumps Win32 submodule.
- - - - -
7dafa40c by Ben Gamari at 2025-07-09T09:44:45-04:00
base: Bump version to 4.22.0
Bumps various submodules.
- - - - -
ef03d8b8 by Rodrigo Mesquita at 2025-07-09T09:45:28-04:00
base: Export displayExceptionWithInfo
This function should be exposed from base following CLC#285
Approved change in CLC#344
Fixes #26058
- - - - -
01d3154e by Wen Kokke at 2025-07-10T17:06:36+01:00
Fix documentation for HEAP_PROF_SAMPLE_STRING
- - - - -
ac259c48 by Wen Kokke at 2025-07-10T17:06:38+01:00
Fix documentation for HEAP_PROF_SAMPLE_COST_CENTRE
- - - - -
2b4db9ba by Pi Delport at 2025-07-11T16:40:52-04:00
(Applicative docs typo: missing "one")
- - - - -
1064d428 by Apoorv Ingle at 2025-07-13T23:24:02-05:00
- Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed.
- Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx`
- `tcXExpr` is less hacky now
- do not look through HsExpansion applications
- kill OrigPat and remove HsThingRn From VAExpansion
- look through XExpr ExpandedThingRn while inferring type of head
- always set in generated code after stepping inside a ExpandedThingRn
- fixing record update error messages
- remove special case of tcbody from tcLambdaMatches
- wrap last stmt expansion in a HsPar so that the error messages are prettier
- remove special case of dsExpr for ExpandedThingTc
- make EExpand (HsExpr GhcRn) instead of EExpand HsThingRn
- fixing error messages for rebindable
- - - - -
08c3422b by Apoorv Ingle at 2025-07-13T23:24:02-05:00
fix the case where head of the application chain is an expanded expression and the argument is a type application c.f. T19167.hs
- - - - -
3d9d7755 by Apoorv Ingle at 2025-07-13T23:24:02-05:00
move setQLInstLevel inside tcInstFun
- - - - -
e0d2cee3 by Apoorv Ingle at 2025-07-13T23:24:02-05:00
ignore ds warnings originating from gen locations
- - - - -
fd973345 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
filter expr stmts error msgs
- - - - -
9cdc7d5d by Apoorv Ingle at 2025-07-13T23:24:03-05:00
exception for AppDo while making error ctxt
- - - - -
06e81188 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
moving around things for locations and error ctxts
- - - - -
2642c7f5 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
popErrCtxt doesn't push contexts and popErrCtxts in the first argument to bind and >> in do expansion statements
- - - - -
b106975a by Apoorv Ingle at 2025-07-13T23:24:03-05:00
accept test cases with changed error messages
-------------------------
Metric Decrease:
T9020
-------------------------
- - - - -
713d39ca by Apoorv Ingle at 2025-07-13T23:24:03-05:00
look through PopErrCtxt while splitting exprs in application chains
- - - - -
180dbc1a by Apoorv Ingle at 2025-07-13T23:24:03-05:00
check the right origin for record selector incomplete warnings
- - - - -
b2781fdf by Apoorv Ingle at 2025-07-13T23:24:03-05:00
kill VAExpansion
- - - - -
d79a6a34 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
pass CtOrigin to tcApp for instantiateSigma
- - - - -
bc8c1310 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
do not suppress pprArising
- - - - -
ca44e03f by Apoorv Ingle at 2025-07-13T23:24:03-05:00
kill VACall
- - - - -
fd6b0693 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
kill AppCtxt
- - - - -
901e421b by Apoorv Ingle at 2025-07-13T23:24:03-05:00
remove addHeadCtxt
- - - - -
9904b6f3 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
fix pprArising for MonadFailErrors
- - - - -
34beb3a0 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
rename ctxt to sloc
- - - - -
ec6a5a12 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
fix RepPolyDoBind error message herald
- - - - -
87b98b93 by Apoorv Ingle at 2025-07-13T23:24:03-05:00
SrcCodeCtxt
more changes
- - - - -
59f3bc6c by Apoorv Ingle at 2025-07-13T23:24:03-05:00
make tcl_in_gen_code a SrcCodeCtxt and rename DoOrigin to DoStmtOrigin
- - - - -
cadafb2d by Apoorv Ingle at 2025-07-13T23:24:03-05:00
make error messages for records saner
- - - - -
65d228aa by Apoorv Ingle at 2025-07-13T23:24:03-05:00
accept the right test output
- - - - -
e691cf3a by Apoorv Ingle at 2025-07-13T23:24:04-05:00
make make sure to set inGenerated code for RecordUpdate checks
- - - - -
8f41ac59 by Apoorv Ingle at 2025-07-13T23:24:04-05:00
rename HsThingRn to SrcCodeOrigin
- - - - -
909aeb20 by Apoorv Ingle at 2025-07-13T23:24:04-05:00
minor lclenv getter setter changes
- - - - -
a4034728 by Apoorv Ingle at 2025-07-13T23:24:04-05:00
fix exprCtOrigin for HsProjection case. It was assigned to be SectionOrigin, but it should be GetFieldOrigin
- - - - -
000adfee by Apoorv Ingle at 2025-07-13T23:24:04-05:00
undo test changes
- - - - -
e44614ef by Apoorv Ingle at 2025-07-13T23:24:04-05:00
fix unused do binding warning error location
- - - - -
aed0281b by Apoorv Ingle at 2025-07-13T23:24:04-05:00
FRRRecordUpdate message change
- - - - -
b45afebd by Apoorv Ingle at 2025-07-13T23:24:04-05:00
- kill tcl_in_gen_code
- It is subsumed by `ErrCtxtStack` which keep tracks of `ErrCtxt` and code ctxt
- - - - -
95fe544c by Apoorv Ingle at 2025-07-13T23:24:04-05:00
kill ExpectedFunTyOrig
- - - - -
b99d0532 by Apoorv Ingle at 2025-07-14T06:57:23-05:00
update argument position number of CtOrigin
- - - - -
8fa065e5 by Apoorv Ingle at 2025-07-14T08:47:52-05:00
fix suggestion in error message for record field and modify herald everywhere
- - - - -
9e825b42 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
- Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed.
- Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx`
- `tcXExpr` is less hacky now
- do not look through HsExpansion applications
- kill OrigPat and remove HsThingRn From VAExpansion
- look through XExpr ExpandedThingRn while inferring type of head
- always set in generated code after stepping inside a ExpandedThingRn
- fixing record update error messages
- remove special case of tcbody from tcLambdaMatches
- wrap last stmt expansion in a HsPar so that the error messages are prettier
- remove special case of dsExpr for ExpandedThingTc
- make EExpand (HsExpr GhcRn) instead of EExpand HsThingRn
- fixing error messages for rebindable
- - - - -
b349fbc3 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
fix the case where head of the application chain is an expanded expression and the argument is a type application c.f. T19167.hs
- - - - -
f31fb7a9 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
move setQLInstLevel inside tcInstFun
- - - - -
a0c5e362 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
ignore ds warnings originating from gen locations
- - - - -
e52c4fa0 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
filter expr stmts error msgs
- - - - -
9419653b by Apoorv Ingle at 2025-07-14T08:49:36-05:00
exception for AppDo while making error ctxt
- - - - -
7d36be39 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
moving around things for locations and error ctxts
- - - - -
2a92c679 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
popErrCtxt doesn't push contexts and popErrCtxts in the first argument to bind and >> in do expansion statements
- - - - -
b656de1b by Apoorv Ingle at 2025-07-14T08:49:36-05:00
accept test cases with changed error messages
-------------------------
Metric Decrease:
T9020
-------------------------
- - - - -
33ea0cbb by Apoorv Ingle at 2025-07-14T08:49:36-05:00
look through PopErrCtxt while splitting exprs in application chains
- - - - -
17d30b7a by Apoorv Ingle at 2025-07-14T08:49:36-05:00
check the right origin for record selector incomplete warnings
- - - - -
31563a38 by Apoorv Ingle at 2025-07-14T08:49:36-05:00
kill VAExpansion
- - - - -
8b26f06a by Apoorv Ingle at 2025-07-14T08:49:36-05:00
pass CtOrigin to tcApp for instantiateSigma
- - - - -
b7cbe082 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
do not suppress pprArising
- - - - -
a1861e4e by Apoorv Ingle at 2025-07-14T08:49:37-05:00
kill VACall
- - - - -
d30865b6 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
kill AppCtxt
- - - - -
6644d216 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
remove addHeadCtxt
- - - - -
220796c2 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
fix pprArising for MonadFailErrors
- - - - -
6254331e by Apoorv Ingle at 2025-07-14T08:49:37-05:00
rename ctxt to sloc
- - - - -
8b3fef84 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
fix RepPolyDoBind error message herald
- - - - -
bdb7f86c by Apoorv Ingle at 2025-07-14T08:49:37-05:00
SrcCodeCtxt
more changes
- - - - -
4e425456 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
make tcl_in_gen_code a SrcCodeCtxt and rename DoOrigin to DoStmtOrigin
- - - - -
007f77d5 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
make error messages for records saner
- - - - -
eafdd22a by Apoorv Ingle at 2025-07-14T08:49:37-05:00
accept the right test output
- - - - -
c71e964c by Apoorv Ingle at 2025-07-14T08:49:37-05:00
make make sure to set inGenerated code for RecordUpdate checks
- - - - -
557457ae by Apoorv Ingle at 2025-07-14T08:49:37-05:00
rename HsThingRn to SrcCodeOrigin
- - - - -
463299c7 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
minor lclenv getter setter changes
- - - - -
d1403d5d by Apoorv Ingle at 2025-07-14T08:49:37-05:00
fix exprCtOrigin for HsProjection case. It was assigned to be SectionOrigin, but it should be GetFieldOrigin
- - - - -
dd183672 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
undo test changes
- - - - -
1db7605b by Apoorv Ingle at 2025-07-14T08:49:37-05:00
fix unused do binding warning error location
- - - - -
3404369c by Apoorv Ingle at 2025-07-14T08:49:37-05:00
FRRRecordUpdate message change
- - - - -
72722d05 by Apoorv Ingle at 2025-07-14T08:49:37-05:00
- kill tcl_in_gen_code
- It is subsumed by `ErrCtxtStack` which keep tracks of `ErrCtxt` and code ctxt
- - - - -
577373bd by Apoorv Ingle at 2025-07-14T08:52:00-05:00
Merge branch 'wip/ani/ctorig-stuff' into wip/spj-apporv-Oct24
- - - - -
229 changed files:
- compiler/GHC.hs
- compiler/GHC/Builtin/primops.txt.pp
- compiler/GHC/ByteCode/Asm.hs
- + compiler/GHC/ByteCode/Breakpoints.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Linker.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/Core/FVs.hs
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Map/Expr.hs
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Core/Opt/Simplify/Iteration.hs
- compiler/GHC/Core/Ppr.hs
- compiler/GHC/Core/Subst.hs
- compiler/GHC/Core/Tidy.hs
- compiler/GHC/Core/TyCon.hs
- compiler/GHC/Core/Utils.hs
- compiler/GHC/CoreToIface.hs
- compiler/GHC/CoreToStg.hs
- compiler/GHC/CoreToStg/Prep.hs
- compiler/GHC/Driver/Config.hs
- + compiler/GHC/Driver/Session/Inspect.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Instances.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Linker/Loader.hs
- compiler/GHC/Linker/Types.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Runtime/Debugger/Breakpoints.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Eval/Types.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Interpreter/Types.hs
- compiler/GHC/Stg/BcPrep.hs
- compiler/GHC/Stg/FVs.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Prim.hs
- compiler/GHC/StgToJS/Prim.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- + compiler/GHC/Tc/Gen/App.hs-boot
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Types/ErrCtxt.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/Unify.hs
- − compiler/GHC/Types/Breakpoint.hs
- compiler/GHC/Types/Tickish.hs
- compiler/GHC/Unit/Module/ModGuts.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/eventlog-formats.rst
- docs/users_guide/exts/doandifthenelse.rst
- docs/users_guide/exts/ffi.rst
- docs/users_guide/ghci.rst
- docs/users_guide/using.rst
- ghc/GHCi/UI.hs
- hadrian/src/Oracles/Flag.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Packages.hs
- hadrian/src/Settings/Program.hs
- libraries/Win32
- libraries/array
- libraries/base/base.cabal.in
- libraries/base/changelog.md
- libraries/base/src/Control/Exception.hs
- libraries/binary
- libraries/deepseq
- libraries/directory
- libraries/exceptions
- libraries/filepath
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghc-compact/GHC/Compact.hs
- libraries/ghc-compact/GHC/Compact/Serialized.hs
- libraries/ghc-compact/ghc-compact.cabal
- libraries/ghc-experimental/ghc-experimental.cabal.in
- + libraries/ghc-experimental/src/System/Mem/Experimental.hs
- libraries/ghc-heap/GHC/Exts/Heap/Closures.hs
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc
- libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc
- libraries/ghc-heap/GHC/Exts/Heap/Utils.hsc
- libraries/ghc-heap/ghc-heap.cabal.in
- libraries/ghc-heap/tests/parse_tso_flags.hs
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/src/GHC/Internal/AllocationLimitHandler.hs
- libraries/ghc-internal/src/GHC/Internal/Base.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs
- libraries/ghc-internal/src/GHC/Internal/List.hs
- libraries/ghc-prim/changelog.md
- libraries/ghc-prim/ghc-prim.cabal
- + libraries/ghci/GHCi/Debugger.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/ghci/ghci.cabal.in
- libraries/haskeline
- libraries/hpc
- libraries/os-string
- libraries/parsec
- libraries/process
- libraries/semaphore-compat
- libraries/stm
- libraries/template-haskell/template-haskell.cabal.in
- libraries/terminfo
- libraries/text
- libraries/unix
- + rts/AllocArray.c
- + rts/AllocArray.h
- rts/Disassembler.c
- rts/Heap.c
- rts/Interpreter.c
- rts/Interpreter.h
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/RtsStartup.c
- rts/RtsSymbols.c
- rts/RtsUtils.c
- rts/Schedule.c
- rts/StgMiscClosures.cmm
- rts/ThreadLabels.c
- rts/Threads.c
- rts/Weak.c
- rts/external-symbols.list.in
- rts/include/Rts.h
- rts/include/rts/Bytecodes.h
- rts/include/rts/Constants.h
- rts/include/rts/prof/CCS.h
- rts/include/rts/storage/Closures.h
- rts/include/rts/storage/GC.h
- rts/include/rts/storage/Heap.h
- rts/include/rts/storage/TSO.h
- rts/include/stg/MiscClosures.h
- rts/rts.cabal
- rts/sm/Storage.c
- testsuite/tests/backpack/cabal/bkpcabal08/bkpcabal08.stdout
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/default/default-fail05.stderr
- + testsuite/tests/ghci.debugger/scripts/T26042b.hs
- + testsuite/tests/ghci.debugger/scripts/T26042b.script
- + testsuite/tests/ghci.debugger/scripts/T26042b.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042c.hs
- + testsuite/tests/ghci.debugger/scripts/T26042c.script
- + testsuite/tests/ghci.debugger/scripts/T26042c.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042d.hs
- + testsuite/tests/ghci.debugger/scripts/T26042d.script
- + testsuite/tests/ghci.debugger/scripts/T26042d.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042e.hs
- + testsuite/tests/ghci.debugger/scripts/T26042e.script
- + testsuite/tests/ghci.debugger/scripts/T26042e.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042f.hs
- + testsuite/tests/ghci.debugger/scripts/T26042f.script
- + testsuite/tests/ghci.debugger/scripts/T26042f1.stderr
- + testsuite/tests/ghci.debugger/scripts/T26042f1.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042f2.stdout
- + testsuite/tests/ghci.debugger/scripts/T26042g.hs
- + testsuite/tests/ghci.debugger/scripts/T26042g.script
- + testsuite/tests/ghci.debugger/scripts/T26042g.stdout
- testsuite/tests/ghci.debugger/scripts/all.T
- + testsuite/tests/indexed-types/should_fail/T26176.hs
- + testsuite/tests/indexed-types/should_fail/T26176.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- testsuite/tests/indexed-types/should_fail/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-experimental-exports.stdout
- testsuite/tests/interface-stability/ghc-experimental-exports.stdout-mingw32
- testsuite/tests/interface-stability/ghc-prim-exports.stdout
- testsuite/tests/interface-stability/ghc-prim-exports.stdout-mingw32
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/rep-poly/RepPolyRecordUpdate.stderr
- + testsuite/tests/rts/T22859.hs
- + testsuite/tests/rts/T22859.stderr
- testsuite/tests/rts/all.T
- + testsuite/tests/typecheck/should_compile/T14010.hs
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- testsuite/tests/typecheck/should_fail/T3323.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/tcfail102.stderr
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
- utils/haddock/CHANGES.md
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Create.hs
- utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
- utils/haddock/haddock-library/haddock-library.cabal
- utils/haddock/haddock-test/haddock-test.cabal
- utils/haddock/haddock-test/src/Test/Haddock/Config.hs
- utils/haddock/haddock.cabal
- utils/haddock/html-test/ref/Bug1004.html
- + utils/haddock/html-test/ref/Bug25739.html
- + utils/haddock/html-test/src/Bug25739.hs
- utils/hsc2hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2fb3b1ba81aa2bd6d2b2985139638d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2fb3b1ba81aa2bd6d2b2985139638d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/ani/ctorig-stuff] fix suggestion in error message for record field and modify herald everywhere
by Apoorv Ingle (@ani) 14 Jul '25
by Apoorv Ingle (@ani) 14 Jul '25
14 Jul '25
Apoorv Ingle pushed to branch wip/ani/ctorig-stuff at Glasgow Haskell Compiler / GHC
Commits:
8fa065e5 by Apoorv Ingle at 2025-07-14T08:47:52-05:00
fix suggestion in error message for record field and modify herald everywhere
- - - - -
4 changed files:
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Unify.hs
- + compiler/hie.yaml
Changes:
=====================================
compiler/GHC/Tc/Errors.hs
=====================================
@@ -24,6 +24,10 @@ import GHC.Driver.Config.Diagnostic
import GHC.Rename.Unbound
+import Language.Haskell.Syntax (DotFieldOcc (..))
+import Language.Haskell.Syntax.Basic (FieldLabelString (..))
+import GHC.Hs.Expr (SrcCodeOrigin (..), HsExpr (..))
+
import GHC.Tc.Types
import GHC.Tc.Utils.Monad
import GHC.Tc.Errors.Types
@@ -2349,7 +2353,7 @@ mk_dict_err ctxt (item, (matches, pot_unifiers, unsafe_overlapped))
isNothing (lookupLocalRdrOcc lcl_env occ_name)
record_field = case orig of
- GetFieldOrigin name -> Just (mkVarOccFS name)
+ ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ name))) -> Just (mkVarOccFS (field_label $ unLoc $ dfoLabel name))
_ -> Nothing
{- Note [Report candidate instances]
=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -788,7 +788,8 @@ lexprCtOrigin (L _ e) = exprCtOrigin e
exprCtOrigin :: HsExpr GhcRn -> CtOrigin
exprCtOrigin (HsVar _ (L _ (WithUserRdr _ name))) = OccurrenceOf name
-exprCtOrigin (HsGetField _ _ (L _ f)) = GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
+exprCtOrigin e@(HsGetField _ _ (L _ _)) = ExpansionOrigin (OrigExpr e)
+ -- GetFieldOrigin (field_label $ unLoc $ dfoLabel f)
exprCtOrigin (HsOverLabel _ l) = OverLabelOrigin l
exprCtOrigin (ExplicitList {}) = ListOrigin
exprCtOrigin (HsIPVar _ ip) = IPOccOrigin ip
@@ -1081,6 +1082,7 @@ pprCtO (ImpedanceMatching {}) = text "combining required constraints"
pprCtO (NonLinearPatternOrigin _ pat) = hsep [text "a non-linear pattern" <+> quotes (ppr pat)]
pprCtO (ExpansionOrigin (OrigPat p)) = hsep [text "a pattern" <+> quotes (ppr p)]
pprCtO (ExpansionOrigin (OrigStmt{})) = text "a do statement"
+pprCtO (ExpansionOrigin (OrigExpr (HsGetField _ _ (L _ f)))) = hsep [text "selecting the field", quotes (ppr f)]
pprCtO (ExpansionOrigin (OrigExpr e)) = text "an expression" <+> ppr e
pprCtO (ExpectedFunTySyntaxOp{}) = text "a rebindable syntax operator"
pprCtO (ExpectedFunTyViewPat{}) = text "a view pattern"
=====================================
compiler/GHC/Tc/Utils/Unify.hs
=====================================
@@ -174,7 +174,7 @@ matchActualFunTy herald mb_thing err_info fun_ty
go (FunTy { ft_af = af, ft_mult = w, ft_arg = arg_ty, ft_res = res_ty })
= assert (isVisibleFunArg af) $
- do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy herald 1) arg_ty
+ do { hasFixedRuntimeRep_syntactic (FRRExpectedFunTy (updatePositionCtOrigin 1 herald) 1) arg_ty
; return (idHsWrapper, Scaled w arg_ty, res_ty) }
go ty@(TyVarTy tv)
@@ -852,7 +852,7 @@ matchExpectedFunTys herald ctx arity (Check top_ty) thing_inside
, ft_arg = arg_ty, ft_res = res_ty })
= assert (isVisibleFunArg af) $
do { let arg_pos = arity - n_req + 1 -- 1 for the first argument etc
- ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy herald arg_pos) arg_ty
+ ; (arg_co, arg_ty) <- hasFixedRuntimeRep (FRRExpectedFunTy (updatePositionCtOrigin arg_pos herald) arg_pos) arg_ty
; (wrap_res, result) <- check (n_req - 1)
(mkCheckExpFunPatTy (Scaled mult arg_ty) : rev_pat_tys)
res_ty
=====================================
compiler/hie.yaml
=====================================
@@ -0,0 +1,9 @@
+# This is a IDE configuration file which tells IDEs such as `ghcide` how
+# to set up a GHC API session for this project.
+#
+# To use it in windows systems replace the config with
+# cradle: {bios: {program: "./hadrian/hie-bios.bat"}}
+#
+# The format is documented here - https://github.com/mpickering/hie-bios
+cradle: {bios: {program: "./hadrian/hie-bios",
+ with-ghc: "~/.ghcup/bin/ghc"}}
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8fa065e50b36cd9e8df3fc3ead631ad…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8fa065e50b36cd9e8df3fc3ead631ad…
You're receiving this email because of your account on gitlab.haskell.org.
1
0