
[Git][ghc/ghc][wip/fendor/no-load] Implement `-fno-load-initial-targets` flag
by Hannes Siebenhandl (@fendor) 24 Jun '25
by Hannes Siebenhandl (@fendor) 24 Jun '25
24 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/no-load at Glasgow Haskell Compiler / GHC
Commits:
ea100f16 by fendor at 2025-06-24T17:04:45+02: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`.
- - - - -
35 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Unit/Module/Graph.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- + 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/prog021/all.T
- − testsuite/tests/ghci/prog021/prog021.T
- testsuite/tests/ghci/prog021/prog021.script → testsuite/tests/ghci/prog021/prog021a.script
- testsuite/tests/ghci/prog021/prog021.stderr → testsuite/tests/ghci/prog021/prog021a.stderr
- testsuite/tests/ghci/prog021/prog021.stdout → 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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ea100f163261ca8c40023c305d29438…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ea100f163261ca8c40023c305d29438…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/torsten.schmits/worker-debug] use OsPath for PkgDbPath and UnitDatabase
by Torsten Schmits (@torsten.schmits) 24 Jun '25
by Torsten Schmits (@torsten.schmits) 24 Jun '25
24 Jun '25
Torsten Schmits pushed to branch wip/torsten.schmits/worker-debug at Glasgow Haskell Compiler / GHC
Commits:
19695614 by Torsten Schmits at 2025-06-24T17:01:05+02:00
use OsPath for PkgDbPath and UnitDatabase
- - - - -
4 changed files:
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Unit/State.hs
Changes:
=====================================
compiler/GHC/Driver/Backpack.hs
=====================================
@@ -91,6 +91,7 @@ import Data.Map (Map)
import qualified Data.Map as Map
import qualified Data.Set as Set
import GHC.Types.Error (mkUnknownDiagnostic)
+import System.OsPath (unsafeEncodeUtf)
-- | Entry point to compile a Backpack file.
doBackpack :: [FilePath] -> Ghc ()
@@ -433,7 +434,7 @@ addUnit u = do
Nothing -> panic "addUnit: called too early"
Just dbs ->
let newdb = UnitDatabase
- { unitDatabasePath = "(in memory " ++ showSDoc dflags0 (ppr (unitId u)) ++ ")"
+ { unitDatabasePath = unsafeEncodeUtf $ "(in memory " ++ showSDoc dflags0 (ppr (unitId u)) ++ ")"
, unitDatabaseUnits = [u]
}
in return (dbs ++ [newdb]) -- added at the end because ordering matters
=====================================
compiler/GHC/Driver/DynFlags.hs
=====================================
@@ -134,6 +134,7 @@ import System.IO.Error (catchIOError)
import System.Environment (lookupEnv)
import System.FilePath (normalise, (</>))
import System.Directory
+import System.OsPath (OsPath)
import GHC.Foreign (withCString, peekCString)
import qualified Data.Set as Set
@@ -948,7 +949,7 @@ setDynamicNow dflags0 =
data PkgDbRef
= GlobalPkgDb
| UserPkgDb
- | PkgDbPath FilePath
+ | PkgDbPath OsPath
deriving Eq
-- | Used to differentiate the scope an include needs to apply to.
=====================================
compiler/GHC/Driver/Session.hs
=====================================
@@ -278,6 +278,7 @@ import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Word
import System.FilePath
+import System.OsPath (unsafeEncodeUtf)
import Text.ParserCombinators.ReadP hiding (char)
import Text.ParserCombinators.ReadP as R
@@ -1962,7 +1963,7 @@ package_flags_deps :: [(Deprecation, Flag (CmdLineP DynFlags))]
package_flags_deps = [
------- Packages ----------------------------------------------------
make_ord_flag defFlag "package-db"
- (HasArg (addPkgDbRef . PkgDbPath))
+ (HasArg (addPkgDbRef . PkgDbPath . unsafeEncodeUtf))
, make_ord_flag defFlag "clear-package-db" (NoArg clearPkgDb)
, make_ord_flag defFlag "no-global-package-db" (NoArg removeGlobalPkgDb)
, make_ord_flag defFlag "no-user-package-db" (NoArg removeUserPkgDb)
@@ -1972,7 +1973,7 @@ package_flags_deps = [
(NoArg (addPkgDbRef UserPkgDb))
-- backwards compat with GHC<=7.4 :
, make_dep_flag defFlag "package-conf"
- (HasArg $ addPkgDbRef . PkgDbPath) "Use -package-db instead"
+ (HasArg $ addPkgDbRef . PkgDbPath . unsafeEncodeUtf) "Use -package-db instead"
, make_dep_flag defFlag "no-user-package-conf"
(NoArg removeUserPkgDb) "Use -no-user-package-db instead"
, make_ord_flag defGhcFlag "package-name" (HasArg $ \name ->
@@ -3377,7 +3378,7 @@ parseEnvFile :: FilePath -> String -> DynP ()
parseEnvFile envfile = mapM_ parseEntry . lines
where
parseEntry str = case words str of
- ("package-db": _) -> addPkgDbRef (PkgDbPath (envdir </> db))
+ ("package-db": _) -> addPkgDbRef (PkgDbPath (unsafeEncodeUtf (envdir </> db)))
-- relative package dbs are interpreted relative to the env file
where envdir = takeDirectory envfile
db = drop 11 str
=====================================
compiler/GHC/Unit/State.hs
=====================================
@@ -109,6 +109,8 @@ import GHC.Utils.Exception
import System.Directory
import System.FilePath as FilePath
+import System.OsPath (OsPath, decodeUtf, unsafeEncodeUtf)
+import qualified System.OsPath as OsPath
import Control.Monad
import Data.Graph (stronglyConnComp, SCC(..))
import Data.Char ( toUpper )
@@ -405,7 +407,7 @@ initUnitConfig dflags cached_dbs home_units =
where
offsetPackageDb :: Maybe FilePath -> PackageDBFlag -> PackageDBFlag
- offsetPackageDb (Just offset) (PackageDB (PkgDbPath p)) | isRelative p = PackageDB (PkgDbPath (offset </> p))
+ offsetPackageDb (Just offset) (PackageDB (PkgDbPath p)) | OsPath.isRelative p = PackageDB (PkgDbPath (OsPath.unsafeEncodeUtf offset OsPath.</> p))
offsetPackageDb _ p = p
@@ -500,12 +502,12 @@ emptyUnitState = UnitState {
-- | Unit database
data UnitDatabase unit = UnitDatabase
- { unitDatabasePath :: FilePath
+ { unitDatabasePath :: OsPath
, unitDatabaseUnits :: [GenUnitInfo unit]
}
instance Outputable u => Outputable (UnitDatabase u) where
- ppr (UnitDatabase fp _u) = text "DB:" <+> text fp
+ ppr (UnitDatabase fp _u) = text "DB:" <+> text (fromMaybe "invalid path" (decodeUtf fp))
type UnitInfoMap = UniqMap UnitId UnitInfo
@@ -720,9 +722,9 @@ getUnitDbRefs cfg = do
Left _ -> system_conf_refs
Right path
| Just (xs, x) <- snocView path, isSearchPathSeparator x
- -> map PkgDbPath (splitSearchPath xs) ++ system_conf_refs
+ -> map (PkgDbPath . unsafeEncodeUtf) (splitSearchPath xs) ++ system_conf_refs
| otherwise
- -> map PkgDbPath (splitSearchPath path)
+ -> map (PkgDbPath . unsafeEncodeUtf) (splitSearchPath path)
-- Apply the package DB-related flags from the command line to get the
-- final list of package DBs.
@@ -758,7 +760,7 @@ resolveUnitDatabase cfg UserPkgDb = runMaybeT $ do
let pkgconf = dir </> unitConfigDBName cfg
exist <- tryMaybeT $ doesDirectoryExist pkgconf
if exist then return pkgconf else mzero
-resolveUnitDatabase _ (PkgDbPath name) = return $ Just name
+resolveUnitDatabase _ (PkgDbPath name) = return $ Just (fromMaybe undefined (decodeUtf name))
readUnitDatabase :: Logger -> UnitConfig -> FilePath -> IO (UnitDatabase UnitId)
readUnitDatabase logger cfg conf_file = do
@@ -790,7 +792,7 @@ readUnitDatabase logger cfg conf_file = do
pkg_configs1 = map (mungeUnitInfo top_dir pkgroot . mapUnitInfo (\(UnitKey x) -> UnitId x) . mkUnitKeyInfo)
proto_pkg_configs
--
- return $ UnitDatabase conf_file' pkg_configs1
+ return $ UnitDatabase (unsafeEncodeUtf conf_file') pkg_configs1
where
readDirStyleUnitInfo conf_dir = do
let filename = conf_dir </> "package.cache"
@@ -1388,7 +1390,7 @@ mergeDatabases logger = foldM merge (emptyUniqMap, emptyUniqMap) . zip [1..]
where
merge (pkg_map, prec_map) (i, UnitDatabase db_path db) = do
debugTraceMsg logger 2 $
- text "loading package database" <+> text db_path
+ text "loading package database" <+> text (fromMaybe "invalid path" (decodeUtf db_path))
forM_ (Set.toList override_set) $ \pkg ->
debugTraceMsg logger 2 $
text "package" <+> ppr pkg <+>
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19695614f23007e171aaab6943f5840…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19695614f23007e171aaab6943f5840…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: configure: Don't force value of OTOOL, etc. if not present
by Marge Bot (@marge-bot) 24 Jun '25
by Marge Bot (@marge-bot) 24 Jun '25
24 Jun '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
858735ea by Teo Camarasu at 2025-06-24T10:40:23-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
- - - - -
8a325166 by Sylvain Henry at 2025-06-24T10:40:46-04:00
Bump stack resolver to use GHC 9.6.7
Cf #26139
- - - - -
17 changed files:
- distrib/configure.ac.in
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Builder.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/RunTest.hs
- hadrian/stack.yaml
- hadrian/stack.yaml.lock
- libraries/template-haskell/changelog.md
- m4/fp_settings.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- rts/linker/LoadArchive.c
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
Changes:
=====================================
distrib/configure.ac.in
=====================================
@@ -216,7 +216,7 @@ AC_SUBST([LlvmAsCmd])
dnl We know that `clang` supports `--target` and it is necessary to pass it
dnl lest we see #25793.
-if test -z "$LlvmAsFlags" ; then
+if test -z "$LlvmAsFlags" && ! test -z "$LlvmTarget"; then
LlvmAsFlags="--target=$LlvmTarget"
fi
AC_SUBST([LlvmAsFlags])
=====================================
hadrian/cfg/default.host.target.in
=====================================
@@ -38,5 +38,10 @@ Target
, tgtRanlib = Nothing
, tgtNm = Nm {nmProgram = Program {prgPath = "", prgFlags = []}}
, tgtMergeObjs = Just (MergeObjs {mergeObjsProgram = Program {prgPath = "@LD_STAGE0@", prgFlags = ["-r"]}, mergeObjsSupportsResponseFiles = False})
+, tgtLlc = Nothing
+, tgtOpt = Nothing
+, tgtLlvmAs = Nothing
, tgtWindres = Nothing
+, tgtOtool = Nothing
+, tgtInstallNameTool = Nothing
}
=====================================
hadrian/cfg/default.target.in
=====================================
@@ -38,5 +38,10 @@ Target
, tgtRanlib = Just (Ranlib {ranlibProgram = Program {prgPath = "@RanlibCmd@", prgFlags = []}})
, tgtNm = Nm {nmProgram = Program {prgPath = "@NmCmd@", prgFlags = []}}
, tgtMergeObjs = @MergeObjsCmdMaybe@
+, tgtLlc = @LlcCmdMaybeProg@
+, tgtOpt = @OptCmdMaybeProg@
+, tgtLlvmAs = @LlvmAsCmdMaybeProg@
, tgtWindres = @WindresCmdMaybeProg@
+, tgtOtool = @OtoolCmdMaybeProg@
+, tgtInstallNameTool = @InstallNameToolCmdMaybeProg@
}
=====================================
hadrian/cfg/system.config.in
=====================================
@@ -79,13 +79,6 @@ 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-otool-command = @SettingsOtoolCommand@
-settings-install_name_tool-command = @SettingsInstallNameToolCommand@
-settings-llc-command = @SettingsLlcCommand@
-settings-opt-command = @SettingsOptCommand@
-settings-llvm-as-command = @SettingsLlvmAsCommand@
-settings-llvm-as-flags = @SettingsLlvmAsFlags@
settings-use-distro-mingw = @SettingsUseDistroMINGW@
target-has-libm = @TargetHasLibm@
=====================================
hadrian/src/Builder.hs
=====================================
@@ -34,7 +34,6 @@ import Base
import Context
import Oracles.Flag
import Oracles.Setting (setting, Setting(..))
-import Oracles.Setting (settingsFileSetting, ToolchainSetting(..))
import Packages
import GHC.IO.Encoding (getFileSystemEncoding)
@@ -240,7 +239,7 @@ instance H.Builder Builder where
Ghc _ st -> do
root <- buildRoot
unlitPath <- builderPath Unlit
- distro_mingw <- settingsFileSetting ToolchainSetting_DistroMinGW
+ distro_mingw <- lookupSystemConfig "settings-use-distro-mingw"
libffi_adjustors <- useLibffiForAdjustors
use_system_ffi <- flag UseSystemFfi
=====================================
hadrian/src/Oracles/Setting.hs
=====================================
@@ -2,7 +2,6 @@ module Oracles.Setting (
configFile,
-- * Settings
Setting (..), setting, getSetting,
- ToolchainSetting (..), settingsFileSetting,
-- * Helpers
ghcCanonVersion, cmdLineLengthLimit, targetSupportsRPaths, topDirectory,
@@ -75,25 +74,6 @@ data Setting = CursesIncludeDir
| BourneShell
| EmsdkVersion
--- TODO compute solely in Hadrian, removing these variables' definitions
--- from aclocal.m4 whenever they can be calculated from other variables
--- already fed into Hadrian.
-
--- | All 'ToolchainSetting's are computed by the ghc-toolchain utility for configuring toolchains.
--- This used to be defined by 'FP_SETTINGS' in aclocal.m4.
---
--- TODO: We should be able to drop this completely, after moving all the toolchain settings to ghc-toolchain
--- Move to ghc-toolchain and to the Target files generated by configure and ghc-toolchain
--- * First we will get rid of DistroMinGW when we fix the windows build
-data ToolchainSetting
- = ToolchainSetting_OtoolCommand
- | ToolchainSetting_InstallNameToolCommand
- | ToolchainSetting_LlcCommand
- | ToolchainSetting_OptCommand
- | ToolchainSetting_LlvmAsCommand
- | ToolchainSetting_LlvmAsFlags
- | ToolchainSetting_DistroMinGW
-
-- | Look up the value of a 'Setting' in @cfg/system.config@, tracking the
-- result.
setting :: Setting -> Action String
@@ -134,20 +114,6 @@ setting key = lookupSystemConfig $ case key of
BourneShell -> "bourne-shell"
EmsdkVersion -> "emsdk-version"
--- | Look up the value of a 'SettingList' in @cfg/system.config@, tracking the
--- result.
--- See Note [tooldir: How GHC finds mingw on Windows]
--- ROMES:TODO: This should be queryTargetTargetConfig
-settingsFileSetting :: ToolchainSetting -> Action String
-settingsFileSetting key = lookupSystemConfig $ case key of
- ToolchainSetting_OtoolCommand -> "settings-otool-command"
- ToolchainSetting_InstallNameToolCommand -> "settings-install_name_tool-command"
- ToolchainSetting_LlcCommand -> "settings-llc-command"
- ToolchainSetting_OptCommand -> "settings-opt-command"
- ToolchainSetting_LlvmAsCommand -> "settings-llvm-as-command"
- ToolchainSetting_LlvmAsFlags -> "settings-llvm-as-flags"
- ToolchainSetting_DistroMinGW -> "settings-use-distro-mingw" -- ROMES:TODO: This option doesn't seem to be in ghc-toolchain yet. It corresponds to EnableDistroToolchain
-
-- | An expression that looks up the value of a 'Setting' in @cfg/system.config@,
-- tracking the result.
getSetting :: Setting -> Expr c b String
=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -424,7 +424,7 @@ bindistRules = do
, interpolateSetting "LlvmMinVersion" LlvmMinVersion
, interpolateVar "LlvmTarget" $ getTarget tgtLlvmTarget
, interpolateSetting "ProjectVersion" ProjectVersion
- , interpolateVar "SettingsUseDistroMINGW" $ settingsFileSetting ToolchainSetting_DistroMinGW
+ , interpolateVar "SettingsUseDistroMINGW" $ lookupSystemConfig "settings-use-distro-mingw"
, interpolateVar "TablesNextToCode" $ yesNo <$> getTarget tgtTablesNextToCode
, interpolateVar "TargetHasLibm" $ lookupSystemConfig "target-has-libm"
, interpolateVar "TargetPlatform" $ getTarget targetPlatformTriple
@@ -508,9 +508,9 @@ generateSettings settingsFile = do
, ("ar flags", queryTarget arFlags)
, ("ar supports at file", queryTarget arSupportsAtFile')
, ("ar supports -L", queryTarget arSupportsDashL')
- , ("ranlib command", queryTarget ranlibPath)
- , ("otool command", expr $ settingsFileSetting ToolchainSetting_OtoolCommand)
- , ("install_name_tool command", expr $ settingsFileSetting ToolchainSetting_InstallNameToolCommand)
+ , ("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)
@@ -525,11 +525,11 @@ generateSettings settingsFile = do
, ("target has libm", expr $ lookupSystemConfig "target-has-libm")
, ("Unregisterised", queryTarget (yesNo . tgtUnregisterised))
, ("LLVM target", queryTarget tgtLlvmTarget)
- , ("LLVM llc command", expr $ settingsFileSetting ToolchainSetting_LlcCommand)
- , ("LLVM opt command", expr $ settingsFileSetting ToolchainSetting_OptCommand)
- , ("LLVM llvm-as command", expr $ settingsFileSetting ToolchainSetting_LlvmAsCommand)
- , ("LLVM llvm-as flags", expr $ settingsFileSetting ToolchainSetting_LlvmAsFlags)
- , ("Use inplace MinGW toolchain", expr $ settingsFileSetting ToolchainSetting_DistroMinGW)
+ , ("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))
@@ -571,10 +571,16 @@ generateSettings settingsFile = do
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
=====================================
hadrian/src/Settings/Builders/RunTest.hs
=====================================
@@ -127,9 +127,9 @@ inTreeCompilerArgs stg = do
platform <- queryTargetTarget targetPlatformTriple
wordsize <- show @Int . (*8) <$> queryTargetTarget (wordSize2Bytes . tgtWordSize)
- llc_cmd <- settingsFileSetting ToolchainSetting_LlcCommand
- llvm_as_cmd <- settingsFileSetting ToolchainSetting_LlvmAsCommand
- have_llvm <- liftIO (all isJust <$> mapM findExecutable [llc_cmd, llvm_as_cmd])
+ llc_cmd <- queryTargetTarget tgtLlc
+ llvm_as_cmd <- queryTargetTarget tgtLlvmAs
+ let have_llvm = all isJust [llc_cmd, llvm_as_cmd]
top <- topDirectory
=====================================
hadrian/stack.yaml
=====================================
@@ -1,6 +1,6 @@
-# GHC's configure script reports that GHC versions 9.2 and greater are required
+# GHC's configure script reports that GHC versions 9.6 and greater are required
# to build GHC from source.
-resolver: lts-20.26 # GHC 9.2.8
+resolver: lts-22.44 # GHC 9.6.7
packages:
- '.'
=====================================
hadrian/stack.yaml.lock
=====================================
@@ -5,22 +5,57 @@
packages:
- completed:
- hackage: Cabal-3.10.1.0@sha256:6d11adf7847d9734e7b02785ff831b5a0d11536bfbcefd6634b2b08411c63c94,12316
+ hackage: Cabal-3.14.0.0@sha256:604ea78fd41acf5382d3578aad5e90d66065a823fca4207ed144ef209daf3c7f,13720
pantry-tree:
- sha256: 3d175ab2e29f17494599bf5844d0037d01fd04287ac5d50c5c788b0633a8ee6f
- size: 9223
+ sha256: 9bd496dbb7d0a1bc1e9147cedbede83003c86ceec66c06594fe292710618bc43
+ size: 12219
original:
- hackage: Cabal-3.10.1.0
+ hackage: Cabal-3.14.0.0
- completed:
- hackage: Cabal-syntax-3.10.1.0@sha256:bb835ebab577fd0f9c11dab96210dbb8d68ffc62652576f4b092563c345930e7,7434
+ hackage: Cabal-syntax-3.14.0.0@sha256:6cd7666c675c29981392d031a9ad402f578234b6195a304c886b84510b0c21cd,7380
pantry-tree:
- sha256: bb1e418f0eb0976bbf4f50491ef4f2b737121bb866e22d07cff1de91f199db7e
- size: 11052
+ sha256: 2aed3c4195554d93ed1e25c4bacdf8eb7f3e006622bbd17a2e27d4bd0de0cd32
+ size: 10977
original:
- hackage: Cabal-syntax-3.10.1.0
+ hackage: Cabal-syntax-3.14.0.0
+- completed:
+ hackage: directory-1.3.9.0@sha256:2490137bb7738bd79392959458ef5f276219ea5ba8a9a56d3e0b06315c1bb917,3307
+ pantry-tree:
+ sha256: cf35b0c2755674f913078c588c88fc169d928ce09f292c648af9f1dbc3167131
+ size: 3386
+ original:
+ hackage: directory-1.3.9.0
+- completed:
+ hackage: file-io-0.1.4@sha256:e3e1866eab82cb28f6a5f28507643da3987008b737e66a3c7398f39f16d824dc,3251
+ pantry-tree:
+ sha256: f5401e2f822eafa465b8c661303275ebcbfd6c0a34a9943379b8f580da64af03
+ size: 858
+ original:
+ hackage: file-io-0.1.4
+- completed:
+ hackage: filepath-1.4.300.2@sha256:24f794247fcb8d26388aaec87b8e3577649f462a744bb09f01e85a60a435d5ab,6128
+ pantry-tree:
+ sha256: 086c1298421eaf07ca46666938bcb750ccbdcf386410e7d597f76d313d3ce98c
+ size: 3998
+ original:
+ hackage: filepath-1.4.300.2
+- completed:
+ hackage: process-1.6.25.0@sha256:092ab61596e914d21983aa2e9206a74c4faa38a5a636446b5c954305821cb496,2749
+ pantry-tree:
+ sha256: bdab416d3c454ad716d4fab1ced490cc75330658c1c7c66a0b6f4b3e5125017b
+ size: 1790
+ original:
+ hackage: process-1.6.25.0
+- completed:
+ hackage: unix-2.8.5.1@sha256:3f702a252a313a7bcb56e3908a14e7f9f1b40e41b7bdc8ae8a9605a1a8686f06,9808
+ pantry-tree:
+ sha256: b961320db69795a16c4ef4eebb0a3e7ddbbbe506fa1e22dde95ee8d8501bfbe5
+ size: 5821
+ original:
+ hackage: unix-2.8.5.1
snapshots:
- completed:
- size: 650475
- url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/mast…
- sha256: 5a59b2a405b3aba3c00188453be172b85893cab8ebc352b1ef58b0eae5d248a2
- original: lts-20.26
+ sha256: 238fa745b64f91184f9aa518fe04bdde6552533d169b0da5256670df83a0f1a9
+ size: 721141
+ url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/mast…
+ original: lts-22.44
=====================================
libraries/template-haskell/changelog.md
=====================================
@@ -12,9 +12,9 @@
`pragSpecInlED`.
* Remove the `Language.Haskell.TH.Lib.Internal` module. This module has long been deprecated, and exposes compiler internals.
- Users should use `Language.Haskell.TH.Lib` instead, which exposes a stable version of this API.
+ Users should use `Language.Haskell.TH.Lib` instead, which exposes a more stable version of this API.
- * Remove `addrToByteArrayName` and `addrToByteArray` from `Language.Haskell.TH.Syntax`. These were part of the implementation of the `Lift ByteArray` instance and were errornously exported because this module lacked an explicit export list. They have no usages on Hackage.
+ * Remove `addrToByteArrayName` and `addrToByteArray` from `Language.Haskell.TH.Syntax`. These were part of the implementation of the `Lift ByteArray` instance and were accidentally exported because this module lacked an explicit export list. They have no usages on Hackage.
## 2.23.0.0
=====================================
m4/fp_settings.m4
=====================================
@@ -136,14 +136,7 @@ AC_DEFUN([FP_SETTINGS],
fi
# Mac-only tools
- if test -z "$OtoolCmd"; then
- OtoolCmd="otool"
- fi
SettingsOtoolCommand="$OtoolCmd"
-
- if test -z "$InstallNameToolCmd"; then
- InstallNameToolCmd="install_name_tool"
- fi
SettingsInstallNameToolCommand="$InstallNameToolCmd"
SettingsCCompilerSupportsNoPie="$CONF_GCC_SUPPORTS_NO_PIE"
=====================================
m4/ghc_toolchain.m4
=====================================
@@ -107,6 +107,9 @@ AC_DEFUN([FIND_GHC_TOOLCHAIN],
echo "--merge-objs=$MergeObjsCmd" >> acargs
echo "--readelf=$READELF" >> acargs
echo "--windres=$WindresCmd" >> acargs
+ echo "--llc=$LlcCmd" >> acargs
+ echo "--opt=$OptCmd" >> acargs
+ echo "--llvm-as=$LlvmAsCmd" >> acargs
if test -n "$USER_LD"; then
echo "--ld=$USER_LD" >> acargs
=====================================
m4/prep_target_file.m4
=====================================
@@ -10,6 +10,38 @@
# This toolchain will additionally be used to validate the one generated by
# ghc-toolchain. See Note [ghc-toolchain consistency checking].
+# PREP_LIST
+# ============
+#
+# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a
+# space-separated list of args
+# i.e.
+# "arg1 arg2 arg3"
+# ==>
+# ["arg1","arg2","arg3"]
+#
+# $1 = list variable to substitute
+dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'.
+AC_DEFUN([PREP_LIST],[
+ # shell array
+ set -- $$1
+ $1List="@<:@"
+ if test "[$]#" -eq 0; then
+ # no arguments
+ true
+ else
+ $1List="${$1List}\"[$]1\""
+ shift # drop first elem
+ for arg in "[$]@"
+ do
+ $1List="${$1List},\"$arg\""
+ done
+ fi
+ $1List="${$1List}@:>@"
+
+ AC_SUBST([$1List])
+])
+
# PREP_MAYBE_SIMPLE_PROGRAM
# =========================
#
@@ -27,6 +59,25 @@ AC_DEFUN([PREP_MAYBE_SIMPLE_PROGRAM],[
AC_SUBST([$1MaybeProg])
])
+# PREP_MAYBE_PROGRAM
+# =========================
+#
+# Introduce a substitution [$1MaybeProg] with
+# * Nothing, if $$1 is empty
+# * Just (Program {prgPath = "$$1", prgFlags = [elements of $$2]}), otherwise
+#
+# $1 = optional program path
+# $2 = program arguments
+AC_DEFUN([PREP_MAYBE_PROGRAM],[
+ if test -z "$$1"; then
+ $1MaybeProg=Nothing
+ else
+ PREP_LIST([$2])
+ $1MaybeProg="Just (Program {prgPath = \"$$1\", prgFlags = $$2List})"
+ fi
+ AC_SUBST([$1MaybeProg])
+])
+
# PREP_MAYBE_STRING
# =========================
#
@@ -86,38 +137,6 @@ AC_DEFUN([PREP_NOT_BOOLEAN],[
AC_SUBST([Not$1Bool])
])
-# PREP_LIST
-# ============
-#
-# Issue a substitution with ["list","of","args"] of [$1List] when $1 is a
-# space-separated list of args
-# i.e.
-# "arg1 arg2 arg3"
-# ==>
-# ["arg1","arg2","arg3"]
-#
-# $1 = list variable to substitute
-dnl In autoconf, '@<:@' stands for '[', and '@:>@' for ']'.
-AC_DEFUN([PREP_LIST],[
- # shell array
- set -- $$1
- $1List="@<:@"
- if test "[$]#" -eq 0; then
- # no arguments
- true
- else
- $1List="${$1List}\"[$]1\""
- shift # drop first elem
- for arg in "[$]@"
- do
- $1List="${$1List},\"$arg\""
- done
- fi
- $1List="${$1List}@:>@"
-
- AC_SUBST([$1List])
-])
-
# Eventually: PREP_BUILD_TARGET_FILE, PREP_HOST_TARGET_FILE, PREP_TARGET_TARGET_FILE
# Prepares required substitutions to generate the target file
AC_DEFUN([PREP_TARGET_FILE],[
@@ -148,7 +167,12 @@ AC_DEFUN([PREP_TARGET_FILE],[
PREP_LIST([JavaScriptCPPArgs])
PREP_LIST([CmmCPPArgs])
PREP_LIST([CmmCPPArgs_STAGE0])
+ PREP_MAYBE_SIMPLE_PROGRAM([LlcCmd])
+ PREP_MAYBE_SIMPLE_PROGRAM([OptCmd])
+ PREP_MAYBE_PROGRAM([LlvmAsCmd], [LlvmAsFlags])
PREP_MAYBE_SIMPLE_PROGRAM([WindresCmd])
+ PREP_MAYBE_SIMPLE_PROGRAM([OtoolCmd])
+ PREP_MAYBE_SIMPLE_PROGRAM([InstallNameToolCmd])
PREP_MAYBE_STRING([TargetVendor_CPP])
PREP_MAYBE_STRING([HostVendor_CPP])
PREP_LIST([CONF_CPP_OPTS_STAGE2])
=====================================
rts/linker/LoadArchive.c
=====================================
@@ -33,6 +33,7 @@
#define DEBUG_LOG(...) IF_DEBUG(linker, debugBelch("loadArchive: " __VA_ARGS__))
+
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
/* Read 4 bytes and convert to host byte order */
static uint32_t read4Bytes(const char buf[static 4])
@@ -40,7 +41,7 @@ static uint32_t read4Bytes(const char buf[static 4])
return ntohl(*(uint32_t*)buf);
}
-static StgBool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
+static bool loadFatArchive(char input[static 20], FILE* f, pathchar* path)
{
uint32_t nfat_arch, nfat_offset, cputype, cpusubtype;
#if defined(i386_HOST_ARCH)
@@ -58,8 +59,9 @@ static StgBool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
#error Unknown Darwin architecture
#endif
- nfat_arch = read4Bytes(tmp + 4);
+ nfat_arch = read4Bytes(input + 4);
DEBUG_LOG("found a fat archive containing %d architectures\n", nfat_arch);
+ char tmp[20];
nfat_offset = 0;
for (uint32_t i = 0; i < nfat_arch; i++) {
/* search for the right arch */
@@ -90,6 +92,7 @@ static StgBool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
}
/* Read the header */
+ char tmp[20];
n = fread(tmp, 1, 8, f);
if (n != 8) {
errorBelch("Failed reading header from `%" PATH_FMT "'", path);
@@ -107,10 +110,51 @@ static StgBool loadFatArchive(char tmp[static 20], FILE* f, pathchar* path)
}
#endif
-static StgBool readThinArchiveMember(int n, int memberSize, pathchar* path,
+enum ObjectFileFormat {
+ NotObject,
+ COFFAmd64,
+ COFFI386,
+ COFFAArch64,
+ ELF,
+ MachO32,
+ MachO64,
+};
+
+static enum ObjectFileFormat identifyObjectFile_(char* buf, size_t sz)
+{
+ if (sz > 2 && ((uint16_t*)buf)[0] == 0x8664) {
+ return COFFAmd64;
+ }
+ if (sz > 2 && ((uint16_t*)buf)[0] == 0x014c) {
+ return COFFI386;
+ }
+ if (sz > 2 && ((uint16_t*)buf)[0] == 0xaa64) {
+ return COFFAArch64;
+ }
+ if (sz > 4 && memcmp(buf, "\x7f" "ELF", 4) == 0) {
+ return ELF;
+ }
+ if (sz > 4 && ((uint32_t*)buf)[0] == 0xfeedface) {
+ return MachO32;
+ }
+ if (sz > 4 && ((uint32_t*)buf)[0] == 0xfeedfacf) {
+ return MachO64;
+ }
+ return NotObject;
+}
+
+static enum ObjectFileFormat identifyObjectFile(FILE *f)
+{
+ char buf[32];
+ ssize_t sz = fread(buf, 1, 32, f);
+ CHECK(fseek(f, -sz, SEEK_CUR) == 0);
+ return identifyObjectFile_(buf, sz);
+}
+
+static bool readThinArchiveMember(int n, int memberSize, pathchar* path,
char* fileName, char* image)
{
- StgBool has_succeeded = false;
+ bool has_succeeded = false;
FILE* member = NULL;
pathchar *pathCopy, *dirName, *memberPath, *objFileName;
memberPath = NULL;
@@ -148,10 +192,9 @@ inner_fail:
return has_succeeded;
}
-static StgBool checkFatArchive(char magic[static 20], FILE* f, pathchar* path)
+static bool checkFatArchive(char magic[static 4], FILE* f, pathchar* path)
{
- StgBool success;
- success = false;
+ bool success = false;
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
/* Not a standard archive, look for a fat archive magic number: */
if (read4Bytes(magic) == FAT_MAGIC)
@@ -175,7 +218,7 @@ static StgBool checkFatArchive(char magic[static 20], FILE* f, pathchar* path)
* be reallocated on return; the old value is now _invalid_.
* @param gnuFileIndexSize The size of the index.
*/
-static StgBool
+static bool
lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_,
char* gnuFileIndex, pathchar* path, size_t* thisFileNameSize,
size_t* fileNameSize)
@@ -241,47 +284,21 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_,
return true;
}
-HsInt loadArchive_ (pathchar *path)
-{
- char *image = NULL;
- HsInt retcode = 0;
- int memberSize;
- int memberIdx = 0;
- FILE *f = NULL;
- int n;
- size_t thisFileNameSize = (size_t)-1; /* shut up bogus GCC warning */
- char *fileName;
- size_t fileNameSize;
- int isObject, isGnuIndex, isThin, isImportLib;
- char tmp[20];
- char *gnuFileIndex;
- int gnuFileIndexSize;
- int misalignment = 0;
-
- DEBUG_LOG("start\n");
- DEBUG_LOG("Loading archive `%" PATH_FMT "'\n", path);
+enum ArchiveFormat {
+ StandardArchive,
+ ThinArchive,
+ FatArchive,
+};
- /* Check that we haven't already loaded this archive.
- Ignore requests to load multiple times */
- if (isAlreadyLoaded(path)) {
- IF_DEBUG(linker,
- debugBelch("ignoring repeated load of %" PATH_FMT "\n", path));
- return 1; /* success */
+static bool identifyArchiveFormat(FILE *f, pathchar *path, enum ArchiveFormat *out)
+{
+ char tmp[8];
+ size_t n = fread(tmp, 1, 8, f);
+ if (n != 8) {
+ errorBelch("loadArchive: Failed reading header from `%" PATH_FMT "'", path); \
+ return false;
}
- gnuFileIndex = NULL;
- gnuFileIndexSize = 0;
-
- fileNameSize = 32;
- fileName = stgMallocBytes(fileNameSize, "loadArchive(fileName)");
-
- isThin = 0;
- isImportLib = 0;
-
- f = pathopen(path, WSTR("rb"));
- if (!f)
- FAIL("loadObj: can't read `%" PATH_FMT "'", path);
-
/* Check if this is an archive by looking for the magic "!<arch>\n"
* string. Usually, if this fails, we belch an error and return. On
* Darwin however, we may have a fat archive, which contains archives for
@@ -300,12 +317,10 @@ HsInt loadArchive_ (pathchar *path)
* its magic "!<arch>\n" string and continue processing just as if
* we had a single architecture archive.
*/
-
- n = fread ( tmp, 1, 8, f );
- if (n != 8) {
- FAIL("Failed reading header from `%" PATH_FMT "'", path);
+ if (strncmp(tmp, "!<arch>\n", 8) == 0) {
+ *out = StandardArchive;
+ return true;
}
- if (strncmp(tmp, "!<arch>\n", 8) == 0) {}
/* Check if this is a thin archive by looking for the magic string "!<thin>\n"
*
* ar thin libraries have the exact same format as normal archives except they
@@ -322,16 +337,59 @@ HsInt loadArchive_ (pathchar *path)
*
*/
else if (strncmp(tmp, "!<thin>\n", 8) == 0) {
- isThin = 1;
+ *out = ThinArchive;
+ return true;
}
else {
- StgBool success = checkFatArchive(tmp, f, path);
- if (!success)
- goto fail;
+ bool success = checkFatArchive(tmp, f, path);
+ if (!success) {
+ return false;
+ }
+ *out = FatArchive;
+ return true;
}
+}
+
+HsInt loadArchive_ (pathchar *path)
+{
+ char *image = NULL;
+ HsInt retcode = 0;
+ int memberIdx = 0;
+ FILE *f = NULL;
+ size_t thisFileNameSize = (size_t) -1; /* shut up bogus GCC warning */
+ int misalignment = 0;
+
+ DEBUG_LOG("start\n");
+ DEBUG_LOG("Loading archive `%" PATH_FMT "'\n", path);
+
+ /* Check that we haven't already loaded this archive.
+ Ignore requests to load multiple times */
+ if (isAlreadyLoaded(path)) {
+ IF_DEBUG(linker,
+ debugBelch("ignoring repeated load of %" PATH_FMT "\n", path));
+ return 1; /* success */
+ }
+
+ char *gnuFileIndex = NULL;
+ int gnuFileIndexSize = 0;
+
+ size_t fileNameSize = 32;
+ char *fileName = stgMallocBytes(fileNameSize, "loadArchive(fileName)");
+
+ f = pathopen(path, WSTR("rb"));
+ if (!f)
+ FAIL("loadObj: can't read `%" PATH_FMT "'", path);
+
+ enum ArchiveFormat archive_fmt;
+ if (!identifyArchiveFormat(f, path, &archive_fmt)) {
+ FAIL("failed to identify archive format of %" PATH_FMT ".", path);
+ }
+ bool isThin = archive_fmt == ThinArchive;
+
DEBUG_LOG("loading archive contents\n");
while (1) {
+ size_t n;
DEBUG_LOG("reading at %ld\n", ftell(f));
n = fread ( fileName, 1, 16, f );
if (n != 16) {
@@ -351,6 +409,7 @@ HsInt loadArchive_ (pathchar *path)
}
#endif
+ char tmp[32];
n = fread ( tmp, 1, 12, f );
if (n != 12)
FAIL("Failed reading mod time from `%" PATH_FMT "'", path);
@@ -369,9 +428,16 @@ HsInt loadArchive_ (pathchar *path)
tmp[10] = '\0';
for (n = 0; isdigit(tmp[n]); n++);
tmp[n] = '\0';
- memberSize = atoi(tmp);
+ size_t memberSize;
+ {
+ char *end;
+ memberSize = strtol(tmp, &end, 10);
+ if (tmp == end) {
+ FAIL("Failed to decode member size");
+ }
+ }
- DEBUG_LOG("size of this archive member is %d\n", memberSize);
+ DEBUG_LOG("size of this archive member is %zd\n", memberSize);
n = fread ( tmp, 1, 2, f );
if (n != 2)
FAIL("Failed reading magic from `%" PATH_FMT "'", path);
@@ -379,7 +445,7 @@ HsInt loadArchive_ (pathchar *path)
FAIL("Failed reading magic from `%" PATH_FMT "' at %ld. Got %c%c",
path, ftell(f), tmp[0], tmp[1]);
- isGnuIndex = 0;
+ bool isGnuIndex = false;
/* Check for BSD-variant large filenames */
if (0 == strncmp(fileName, "#1/", 3)) {
size_t n = 0;
@@ -419,7 +485,7 @@ HsInt loadArchive_ (pathchar *path)
else if (0 == strncmp(fileName, "//", 2)) {
fileName[0] = '\0';
thisFileNameSize = 0;
- isGnuIndex = 1;
+ isGnuIndex = true;
}
/* Check for a file in the GNU file index */
else if (fileName[0] == '/') {
@@ -460,12 +526,8 @@ HsInt loadArchive_ (pathchar *path)
DEBUG_LOG("Found member file `%s'\n", fileName);
- /* TODO: Stop relying on file extensions to determine input formats.
- Instead try to match file headers. See #13103. */
- isObject = (thisFileNameSize >= 2 && strncmp(fileName + thisFileNameSize - 2, ".o" , 2) == 0)
- || (thisFileNameSize >= 3 && strncmp(fileName + thisFileNameSize - 3, ".lo" , 3) == 0)
- || (thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".p_o", 4) == 0)
- || (thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".obj", 4) == 0);
+ bool is_symbol_table = strcmp("", fileName) == 0;
+ enum ObjectFileFormat object_fmt = is_symbol_table ? NotObject : identifyObjectFile(f);
#if defined(OBJFORMAT_PEi386)
/*
@@ -479,15 +541,15 @@ HsInt loadArchive_ (pathchar *path)
*
* Linker members (e.g. filename / are skipped since they are not needed)
*/
- isImportLib = thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".dll", 4) == 0;
+ bool isImportLib = thisFileNameSize >= 4 && strncmp(fileName + thisFileNameSize - 4, ".dll", 4) == 0;
+#else
+ bool isImportLib = false;
#endif // windows
DEBUG_LOG("\tthisFileNameSize = %d\n", (int)thisFileNameSize);
- DEBUG_LOG("\tisObject = %d\n", isObject);
-
- if (isObject) {
- pathchar *archiveMemberName;
+ DEBUG_LOG("\tisObject = %d\n", object_fmt);
+ if ((!is_symbol_table && isThin) || object_fmt != NotObject) {
DEBUG_LOG("Member is an object file...loading...\n");
#if defined(darwin_HOST_OS) || defined(ios_HOST_OS)
@@ -505,14 +567,13 @@ HsInt loadArchive_ (pathchar *path)
image = stgMallocBytes(memberSize, "loadArchive(image)");
#endif
if (isThin) {
- if (!readThinArchiveMember(n, memberSize, path,
- fileName, image)) {
+ if (!readThinArchiveMember(n, memberSize, path, fileName, image)) {
goto fail;
}
}
else
{
- n = fread ( image, 1, memberSize, f );
+ size_t n = fread ( image, 1, memberSize, f );
if (n != memberSize) {
FAIL("error whilst reading `%" PATH_FMT "'", path);
}
@@ -523,16 +584,18 @@ HsInt loadArchive_ (pathchar *path)
// I don't understand why this extra +1 is needed here; pathprintf
// should have given us the correct length but in practice it seems
// to be one byte short on Win32.
- archiveMemberName = stgMallocBytes((size+1+1) * sizeof(pathchar), "loadArchive(file)");
+ pathchar *archiveMemberName = stgMallocBytes((size+1+1) * sizeof(pathchar), "loadArchive(file)");
pathprintf(archiveMemberName, size+1, WSTR("%" PATH_FMT "(#%d:%.*s)"),
path, memberIdx, (int)thisFileNameSize, fileName);
ObjectCode *oc = mkOc(STATIC_OBJECT, path, image, memberSize, false, archiveMemberName,
misalignment);
#if defined(OBJFORMAT_MACHO)
+ ASSERT(object_fmt == MachO32 || object_fmt == MachO64);
ocInit_MachO( oc );
#endif
#if defined(OBJFORMAT_ELF)
+ ASSERT(object_fmt == ELF);
ocInit_ELF( oc );
#endif
@@ -577,7 +640,7 @@ while reading filename from `%" PATH_FMT "'", path);
"Skipping...\n");
n = fseek(f, memberSize, SEEK_CUR);
if (n != 0)
- FAIL("error whilst seeking by %d in `%" PATH_FMT "'",
+ FAIL("error whilst seeking by %zd in `%" PATH_FMT "'",
memberSize, path);
}
#endif
@@ -588,7 +651,7 @@ while reading filename from `%" PATH_FMT "'", path);
if (!isThin || thisFileNameSize == 0) {
n = fseek(f, memberSize, SEEK_CUR);
if (n != 0)
- FAIL("error whilst seeking by %d in `%" PATH_FMT "'",
+ FAIL("error whilst seeking by %zd in `%" PATH_FMT "'",
memberSize, path);
}
}
=====================================
utils/ghc-toolchain/exe/Main.hs
=====================================
@@ -52,7 +52,12 @@ data Opts = Opts
, optNm :: ProgOpt
, optReadelf :: ProgOpt
, optMergeObjs :: ProgOpt
+ , optLlc :: ProgOpt
+ , optOpt :: ProgOpt
+ , optLlvmAs :: ProgOpt
, optWindres :: ProgOpt
+ , optOtool :: ProgOpt
+ , optInstallNameTool :: ProgOpt
-- Note we don't actually configure LD into anything but
-- see #23857 and #22550 for the very unfortunate story.
, optLd :: ProgOpt
@@ -99,8 +104,13 @@ emptyOpts = Opts
, optNm = po0
, optReadelf = po0
, optMergeObjs = po0
+ , optLlc = po0
+ , optOpt = po0
+ , optLlvmAs = po0
, optWindres = po0
, optLd = po0
+ , optOtool = po0
+ , optInstallNameTool = po0
, optUnregisterised = Nothing
, optTablesNextToCode = Nothing
, optUseLibFFIForAdjustors = Nothing
@@ -112,7 +122,8 @@ emptyOpts = Opts
po0 = emptyProgOpt
_optCc, _optCxx, _optCpp, _optHsCpp, _optJsCpp, _optCmmCpp, _optCcLink, _optAr,
- _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optWindres, _optLd
+ _optRanlib, _optNm, _optReadelf, _optMergeObjs, _optLlc, _optOpt, _optLlvmAs,
+ _optWindres, _optLd, _optOtool, _optInstallNameTool
:: Lens Opts ProgOpt
_optCc = Lens optCc (\x o -> o {optCc=x})
_optCxx = Lens optCxx (\x o -> o {optCxx=x})
@@ -126,8 +137,13 @@ _optRanlib = Lens optRanlib (\x o -> o {optRanlib=x})
_optNm = Lens optNm (\x o -> o {optNm=x})
_optReadelf = Lens optReadelf (\x o -> o {optReadelf=x})
_optMergeObjs = Lens optMergeObjs (\x o -> o {optMergeObjs=x})
+_optLlc = Lens optLlc (\x o -> o {optLlc=x})
+_optOpt = Lens optOpt (\x o -> o {optOpt=x})
+_optLlvmAs = Lens optLlvmAs (\x o -> o {optLlvmAs=x})
_optWindres = Lens optWindres (\x o -> o {optWindres=x})
-_optLd = Lens optLd (\x o -> o {optLd= x})
+_optLd = Lens optLd (\x o -> o {optLd=x})
+_optOtool = Lens optOtool (\x o -> o {optOtool=x})
+_optInstallNameTool = Lens optInstallNameTool (\x o -> o {optInstallNameTool=x})
_optTriple :: Lens Opts (Maybe String)
_optTriple = Lens optTriple (\x o -> o {optTriple=x})
@@ -183,8 +199,13 @@ options =
, progOpts "nm" "nm archiver" _optNm
, progOpts "readelf" "readelf utility" _optReadelf
, progOpts "merge-objs" "linker for merging objects" _optMergeObjs
+ , progOpts "llc" "LLVM llc utility" _optLlc
+ , progOpts "opt" "LLVM opt utility" _optOpt
+ , progOpts "llvm-as" "Assembler used for LLVM backend (typically clang)" _optLlvmAs
, progOpts "windres" "windres utility" _optWindres
, progOpts "ld" "linker" _optLd
+ , progOpts "otool" "otool utility" _optOtool
+ , progOpts "install-name-tool" "install-name-tool utility" _optInstallNameTool
]
where
progOpts :: String -> String -> Lens Opts ProgOpt -> [OptDescr (Opts -> Opts)]
@@ -436,6 +457,11 @@ mkTarget opts = do
when (isNothing mergeObjs && not (arSupportsDashL ar)) $
throwE "Neither a object-merging tool (e.g. ld -r) nor an ar that supports -L is available"
+ -- LLVM toolchain
+ llc <- optional $ findProgram "llc" (optLlc opts) ["llc"]
+ opt <- optional $ findProgram "opt" (optOpt opts) ["opt"]
+ llvmAs <- optional $ findProgram "llvm assembler" (optLlvmAs opts) ["clang"]
+
-- Windows-specific utilities
windres <-
case archOS_OS archOs of
@@ -444,6 +470,15 @@ mkTarget opts = do
return (Just windres)
_ -> return Nothing
+ -- Darwin-specific utilities
+ (otool, installNameTool) <-
+ case archOS_OS archOs of
+ OSDarwin -> do
+ otool <- findProgram "otool" (optOtool opts) ["otool"]
+ installNameTool <- findProgram "install_name_tool" (optInstallNameTool opts) ["install_name_tool"]
+ return (Just otool, Just installNameTool)
+ _ -> return (Nothing, Nothing)
+
-- various other properties of the platform
tgtWordSize <- checkWordSize cc
tgtEndianness <- checkEndianness cc
@@ -480,7 +515,12 @@ mkTarget opts = do
, tgtRanlib = ranlib
, tgtNm = nm
, tgtMergeObjs = mergeObjs
+ , tgtLlc = llc
+ , tgtOpt = opt
+ , tgtLlvmAs = llvmAs
, tgtWindres = windres
+ , tgtOtool = otool
+ , tgtInstallNameTool = installNameTool
, tgtWordSize
, tgtEndianness
, tgtUnregisterised
=====================================
utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
=====================================
@@ -22,15 +22,6 @@ data WordSize = WS4 | WS8
data Endianness = LittleEndian | BigEndian
deriving (Show, Read, Eq, Ord)
--- TODO(#23674): Move the remaining relevant `settings-xxx` to Target:
--- * llc command
--- * opt command
--- * install_name_tool
--- * otool command
---
--- Those are all things that are put into GHC's settings, and that might be
--- different across targets
-
-- | A 'Target' consists of:
--
-- * a target architecture and operating system
@@ -72,8 +63,18 @@ data Target = Target
, tgtMergeObjs :: Maybe MergeObjs
-- ^ We don't need a merge objects tool if we @Ar@ supports @-L@
+ -- LLVM backend toolchain
+ , tgtLlc :: Maybe Program
+ , tgtOpt :: Maybe Program
+ , tgtLlvmAs :: Maybe Program
+ -- ^ assembler used to assemble LLVM backend output; typically @clang@
+
-- Windows-specific tools
, tgtWindres :: Maybe Program
+
+ -- Darwin-specific tools
+ , tgtOtool :: Maybe Program
+ , tgtInstallNameTool :: Maybe Program
}
deriving (Read, Eq, Ord)
@@ -121,6 +122,11 @@ instance Show Target where
, ", tgtRanlib = " ++ show tgtRanlib
, ", tgtNm = " ++ show tgtNm
, ", tgtMergeObjs = " ++ show tgtMergeObjs
+ , ", tgtLlc = " ++ show tgtLlc
+ , ", tgtOpt = " ++ show tgtOpt
+ , ", tgtLlvmAs = " ++ show tgtLlvmAs
, ", tgtWindres = " ++ show tgtWindres
+ , ", tgtOtool = " ++ show tgtOtool
+ , ", tgtInstallNameTool = " ++ show tgtInstallNameTool
, "}"
]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bbfc1f7d414c31e1a7d280dc842bae…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bbfc1f7d414c31e1a7d280dc842bae…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/no-load] Implement `-fno-load-initial-targets` flag
by Hannes Siebenhandl (@fendor) 24 Jun '25
by Hannes Siebenhandl (@fendor) 24 Jun '25
24 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/no-load at Glasgow Haskell Compiler / GHC
Commits:
91ce1027 by fendor at 2025-06-24T16:39:23+02: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`.
- - - - -
35 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Unit/Module/Graph.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- + 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/prog021/all.T
- − testsuite/tests/ghci/prog021/prog021.T
- testsuite/tests/ghci/prog021/prog021.script → testsuite/tests/ghci/prog021/prog021a.script
- testsuite/tests/ghci/prog021/prog021.stderr → testsuite/tests/ghci/prog021/prog021a.stderr
- testsuite/tests/ghci/prog021/prog021.stdout → 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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91ce1027727e6865df06f9b1ee9bebf…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/91ce1027727e6865df06f9b1ee9bebf…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/no-load] Implement `-fno-load-initial-targets` flag
by Hannes Siebenhandl (@fendor) 24 Jun '25
by Hannes Siebenhandl (@fendor) 24 Jun '25
24 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/no-load at Glasgow Haskell Compiler / GHC
Commits:
5ce67b3d by fendor at 2025-06-24T16:37:08+02: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`.
- - - - -
35 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Unit/Module/Graph.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- + 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/prog021/all.T
- − testsuite/tests/ghci/prog021/prog021.T
- testsuite/tests/ghci/prog021/prog021.script → testsuite/tests/ghci/prog021/prog021a.script
- testsuite/tests/ghci/prog021/prog021.stderr → testsuite/tests/ghci/prog021/prog021a.stderr
- testsuite/tests/ghci/prog021/prog021.stdout → 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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ce67b3d17664cee3bce14eb7e4cb4c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ce67b3d17664cee3bce14eb7e4cb4c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/no-load] Implement `-fno-load-initial-targets` flag
by Hannes Siebenhandl (@fendor) 24 Jun '25
by Hannes Siebenhandl (@fendor) 24 Jun '25
24 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/no-load at Glasgow Haskell Compiler / GHC
Commits:
1c862156 by fendor at 2025-06-24T16:28:51+02: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`.
- - - - -
35 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Unit/Module/Graph.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- ghc/GHCi/UI/Exception.hs
- + 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/prog021/all.T
- − testsuite/tests/ghci/prog021/prog021.T
- testsuite/tests/ghci/prog021/prog021.script → testsuite/tests/ghci/prog021/prog021a.script
- testsuite/tests/ghci/prog021/prog021.stderr → testsuite/tests/ghci/prog021/prog021a.stderr
- testsuite/tests/ghci/prog021/prog021.stdout → 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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c86215677e2cb919e9e73bb3d97e9c…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c86215677e2cb919e9e73bb3d97e9c…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T18570] 2 commits: Calculate multiplicity for record selector functions
by Sjoerd Visscher (@trac-sjoerd_visscher) 24 Jun '25
by Sjoerd Visscher (@trac-sjoerd_visscher) 24 Jun '25
24 Jun '25
Sjoerd Visscher pushed to branch wip/T18570 at Glasgow Haskell Compiler / GHC
Commits:
4b236bdb by Sjoerd Visscher at 2025-06-24T16:00:45+02:00
Calculate multiplicity for record selector functions
Until now record selector functions always had multiplicity Many, but when all the other fields have been declared with multiplicity Many (including the case when there are no other fields), then the selector function is allowed to be used linearly too, as it is allowed to discard all the other fields. Since in that case the multiplicity can be both One and Many, the selector function is made multiplicity-polymorphic.
- - - - -
131895d5 by Sjoerd Visscher at 2025-06-24T16:00:52+02:00
Test
- - - - -
17 changed files:
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/bugs.rst
- docs/users_guide/exts/linear_types.rst
- + testsuite/tests/linear/should_compile/LinearRecordSelector.hs
- testsuite/tests/linear/should_compile/all.T
- + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs
- + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr
- testsuite/tests/linear/should_fail/all.T
- testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr
- testsuite/tests/overloadedrecflds/should_fail/T23063.stderr
- testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout
- testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr
- testsuite/tests/typecheck/should_fail/CommonFieldTypeMismatch.stderr
- utils/haddock/html-test/ref/Bug294.html
Changes:
=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -44,6 +44,7 @@ module GHC.Core.DataCon (
dataConInstOrigArgTys, dataConRepArgTys, dataConResRepTyArgs,
dataConInstUnivs,
dataConFieldLabels, dataConFieldType, dataConFieldType_maybe,
+ dataConOtherFieldsAllMultMany,
dataConSrcBangs,
dataConSourceArity, dataConVisArity, dataConRepArity,
dataConIsInfix,
@@ -1406,6 +1407,15 @@ dataConFieldType_maybe :: DataCon -> FieldLabelString
dataConFieldType_maybe con label
= find ((== label) . flLabel . fst) (dcFields con `zip` (scaledThing <$> dcOrigArgTys con))
+-- | Check if all the fields of the 'DataCon' have multiplicity 'Many',
+-- except for the given labelled field. In this case the selector
+-- of the given field can be a linear function, since it is allowed
+-- to discard all the other fields.
+dataConOtherFieldsAllMultMany :: DataCon -> FieldLabelString -> Bool
+dataConOtherFieldsAllMultMany con label
+ = all (\(fld, mult) -> flLabel fld == label || isManyTy mult)
+ (dcFields con `zip` (scaledMult <$> dcOrigArgTys con))
+
-- | Strictness/unpack annotations, from user; or, for imported
-- DataCons, from the interface file
-- The list is in one-to-one correspondence with the arity of the 'DataCon'
=====================================
compiler/GHC/Tc/TyCl/PatSyn.hs
=====================================
@@ -841,7 +841,7 @@ mkPatSynRecSelBinds :: PatSyn
-> FieldSelectors
-> [(Id, LHsBind GhcRn)]
mkPatSynRecSelBinds ps fields has_sel
- = [ mkOneRecordSelector [PatSynCon ps] (RecSelPatSyn ps) fld_lbl has_sel
+ = [ mkOneRecordSelector False [PatSynCon ps] (RecSelPatSyn ps) fld_lbl has_sel
| fld_lbl <- fields ]
isUnidirectional :: HsPatSynDir a -> Bool
=====================================
compiler/GHC/Tc/TyCl/Utils.hs
=====================================
@@ -32,7 +32,7 @@ import GHC.Tc.Utils.Env
import GHC.Tc.Gen.Bind( tcValBinds )
import GHC.Tc.Utils.TcType
-import GHC.Builtin.Types( unitTy )
+import GHC.Builtin.Types( unitTy, manyDataConTy, multiplicityTy )
import GHC.Builtin.Uniques ( mkBuiltinUnique )
import GHC.Hs
@@ -71,6 +71,7 @@ import GHC.Types.Name.Env
import GHC.Types.Name.Reader ( mkRdrUnqual )
import GHC.Types.Id
import GHC.Types.Id.Info
+import GHC.Types.Var (mkTyVar)
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Types.Unique.Set
@@ -765,7 +766,8 @@ addTyConsToGblEnv tyclss
do { traceTc "tcAddTyCons" $ vcat
[ text "tycons" <+> ppr tyclss
, text "implicits" <+> ppr implicit_things ]
- ; gbl_env <- tcRecSelBinds (mkRecSelBinds tyclss)
+ -- ; linearEnabled <- xoptM LangExt.LinearTypes
+ ; gbl_env <- tcRecSelBinds (mkRecSelBinds True tyclss)
; th_bndrs <- tcTyThBinders implicit_things
; return (gbl_env, th_bndrs)
}
@@ -848,24 +850,24 @@ tcRecSelBinds sel_bind_prs
, let loc = getSrcSpan sel_id ]
binds = [(NonRecursive, [bind]) | (_, bind) <- sel_bind_prs]
-mkRecSelBinds :: [TyCon] -> [(Id, LHsBind GhcRn)]
+mkRecSelBinds :: Bool -> [TyCon] -> [(Id, LHsBind GhcRn)]
-- NB We produce *un-typechecked* bindings, rather like 'deriving'
-- This makes life easier, because the later type checking will add
-- all necessary type abstractions and applications
-mkRecSelBinds tycons
- = map mkRecSelBind [ (tc,fld) | tc <- tycons
- , fld <- tyConFieldLabels tc ]
+mkRecSelBinds allowMultiplicity tycons
+ = [ mkRecSelBind allowMultiplicity tc fld | tc <- tycons
+ , fld <- tyConFieldLabels tc ]
-mkRecSelBind :: (TyCon, FieldLabel) -> (Id, LHsBind GhcRn)
-mkRecSelBind (tycon, fl)
- = mkOneRecordSelector all_cons (RecSelData tycon) fl
+mkRecSelBind :: Bool -> TyCon -> FieldLabel -> (Id, LHsBind GhcRn)
+mkRecSelBind allowMultiplicity tycon fl
+ = mkOneRecordSelector allowMultiplicity all_cons (RecSelData tycon) fl
FieldSelectors -- See Note [NoFieldSelectors and naughty record selectors]
where
all_cons = map RealDataCon (tyConDataCons tycon)
-mkOneRecordSelector :: [ConLike] -> RecSelParent -> FieldLabel -> FieldSelectors
+mkOneRecordSelector :: Bool -> [ConLike] -> RecSelParent -> FieldLabel -> FieldSelectors
-> (Id, LHsBind GhcRn)
-mkOneRecordSelector all_cons idDetails fl has_sel
+mkOneRecordSelector allowMultiplicity all_cons idDetails fl has_sel
= (sel_id, L (noAnnSrcSpan loc) sel_bind)
where
loc = getSrcSpan sel_name
@@ -916,17 +918,24 @@ mkOneRecordSelector all_cons idDetails fl has_sel
-- thus suppressing making a binding
-- A slight hack!
+ all_other_fields_unrestricted = all all_other_unrestricted all_cons
+ where
+ all_other_unrestricted PatSynCon{} = False
+ all_other_unrestricted (RealDataCon dc) = dataConOtherFieldsAllMultMany dc lbl
+
sel_ty | is_naughty = unitTy -- See Note [Naughty record selectors]
- | otherwise = mkForAllTys sel_tvbs $
+ | otherwise = mkForAllTys (sel_tvbs ++ mult_tvb) $
-- Urgh! See Note [The stupid context] in GHC.Core.DataCon
- mkPhiTy (conLikeStupidTheta con1) $
+ mkPhiTy (conLikeStupidTheta con1) $
-- req_theta is empty for normal DataCon
- mkPhiTy req_theta $
- mkVisFunTyMany data_ty $
- -- Record selectors are always typed with Many. We
- -- could improve on it in the case where all the
- -- fields in all the constructor have multiplicity Many.
+ mkPhiTy req_theta $
+ mkVisFunTy sel_mult data_ty $
field_ty
+ non_partial = length all_cons == length cons_w_field -- See Note [Multiplicity and partial selectors]
+ (mult_tvb, sel_mult) = if allowMultiplicity && non_partial && all_other_fields_unrestricted
+ then ([mkForAllTyBinder (Invisible InferredSpec) mult_var], mkTyVarTy mult_var)
+ else ([], manyDataConTy)
+ mult_var = mkTyVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "m")) multiplicityTy
-- make the binding: sel (C2 { fld = x }) = x
-- sel (C7 { fld = x }) = x
@@ -1165,4 +1174,13 @@ Therefore, when used in the right-hand side of `unT`, GHC attempts to
instantiate `a` with `(forall b. b -> b) -> Int`, which is impredicative.
To make sure that GHC is OK with this, we enable ImpredicativeTypes internally
when typechecking these HsBinds so that the user does not have to.
+
+Note [Multiplicity and partial selectors]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+While all logic for making record selectors multiplicity-polymorphic also applies
+to partial selectors, there is a technical difficulty: the catch-all default case
+that is added throws away its argument, and so cannot be linear. A simple workaround
+was not found. There may exist a more complicated workaround, but the combination of
+linear types and partial selectors is not expected to be very popular in practice, so
+it was decided to not allow multiplicity-polymorphic partial selectors at all.
-}
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -67,6 +67,13 @@ Language
This causes the constructor to have type ``Rec :: Int %'Many -> Char %1 -> Record``.
+ Also record selector functions are now multiplicity-polymorphic when possible.
+ In the above example the selector function ``y`` now has type
+ ``y :: Record %m -> Char``, because the ``x`` field is allowed to be discarded.
+ In particular this always applies to the selector of a newtype wrapper.
+ (Note that in theory this should also work with partial record selectors,
+ but for technical reasons this is not supported.)
+
* The :extension:`ExplicitNamespaces` extension now allows the ``data``
namespace specifier in import and export lists.
=====================================
docs/users_guide/bugs.rst
=====================================
@@ -701,6 +701,9 @@ Bugs in GHC
- Because of a toolchain limitation we are unable to support full Unicode paths
on Windows. On Windows we support up to Latin-1. See :ghc-ticket:`12971` for more.
+- For technical reasons, partial record selectors cannot be made
+ multiplicity-polymorphic, so they are always unrestricted.
+
.. _bugs-ghci:
Bugs in GHCi (the interactive GHC)
=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -238,7 +238,7 @@ to use ``MkT1`` in higher order functions. The additional multiplicity
argument ``m`` is marked as inferred (see
:ref:`inferred-vs-specified`), so that there is no conflict with
visible type application. When displaying types, unless
-``-XLinearTypes`` is enabled, multiplicity polymorphic functions are
+``-XLinearTypes`` is enabled, multiplicity-polymorphic functions are
printed as regular functions (see :ref:`printing-linear-types`);
therefore constructors appear to have regular function types.
@@ -256,21 +256,33 @@ using GADT syntax or record syntax. Given
::
data T2 a b c where
- MkT2 :: a -> b %1 -> c %1 -> T2 a b c -- Note unrestricted arrow in the first argument
+ MkT2 :: a -> b %1 -> c -> T2 a b c -- Note the unrestricted arrows on a and c
-the value ``MkT2 x y z`` can be constructed only if ``x`` is
-unrestricted. On the other hand, a linear function which is matching
-on ``MkT2 x y z`` must consume ``y`` and ``z`` exactly once, but there
-is no restriction on ``x``. The same example can be written using record syntax:
+the value ``MkT2 x y z`` can be constructed only if ``x`` and
+``z`` are unrestricted. On the other hand, a linear function which is
+matching on ``MkT2 x y z`` must consume ``y`` exactly once, but there
+is no restriction on ``x`` and ``z``.
+The same example can be written using record syntax:
::
- data T2 a b c = MkT2 { x %'Many :: a, y :: b, z :: c }
+ data T2 a b c = MkT2 { x %'Many :: a, y :: b, z %'Many :: c }
Again, the constructor ``MkT2`` has type ``MkT2 :: a -> b %1 -> c %1 -> T2 a b c``.
Note that by default record fields are linear, only unrestricted fields
-require a multiplicity annotation. The annotation has no effect on the record selectors.
-So ``x`` has type ``x :: T2 a b c -> a`` and similarly ``y`` has type ``y :: T2 a b c -> b``.
+require a multiplicity annotation.
+
+The multiplicity of record selectors is inferred from the multiplicity of the fields. Note that
+the effect of a selector is to discard all the other fields, so it can only be linear if all the
+other fields are unrestricted. So ``x`` has type ``x :: T2 a b c -> a``, because the ``y`` field
+is not unrestricted. But the ``x`` and ``z`` fields are unrestricted, so the selector for ``y``
+can be linear, and therefore it is made to be multiplicity-polymorphic: ``y :: T2 a b c %m -> b``.
+In particular this always applies to the selector of a newtype wrapper.
+
+In the case of multiple constructors, this logic is repeated for each constructor. So a selector
+is only made multiplicity-polymorphic if for every constructor all the other fields are unrestricted.
+(For technical reasons, partial record selectors cannot be made multiplicity-polymorphic, so they
+are always unrestricted.)
It is also possible to define a multiplicity-polymorphic field:
=====================================
testsuite/tests/linear/should_compile/LinearRecordSelector.hs
=====================================
@@ -0,0 +1,21 @@
+{-# LANGUAGE LinearTypes, DataKinds, OverloadedRecordDot, RebindableSyntax #-}
+module LinearRecordSelector where
+
+import GHC.Exts (Multiplicity(..))
+import Prelude
+
+data Test = A { test :: Int, test2 %Many :: String } | B { test %Many :: Int, test3 %Many :: Char }
+
+test1 :: Test %1 -> Int
+test1 a = test a
+
+testM :: Test -> Int
+testM a = test a
+
+testX :: Test %m -> Int
+testX = test
+
+newtype NT = NT { unNT :: Int }
+
+nt :: NT %m -> Int
+nt a = unNT a
=====================================
testsuite/tests/linear/should_compile/all.T
=====================================
@@ -36,6 +36,7 @@ test('LinearTH3', normal, compile, [''])
test('LinearTH4', req_th, compile, [''])
test('LinearHole', normal, compile, [''])
test('LinearDataConSections', normal, compile, [''])
+test('LinearRecordSelector', normal, compile, ['-dcore-lint'])
test('T18731', normal, compile, [''])
test('T19400', unless(compiler_debugged(), skip), compile, [''])
test('T20023', normal, compile, [''])
=====================================
testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE LinearTypes, DataKinds, OverloadedRecordDot, RebindableSyntax #-}
+module LinearRecordSelector where
+
+import GHC.Exts (Multiplicity(..))
+import Prelude
+
+data Test1 = A1 { testA11 :: Int, testA12 :: String }
+
+-- Fails because testA12 is linear
+test1 :: Test1 %1 -> Int
+test1 a = testA11 a
+
+data Test2 = A2 { testA2 :: Int } | B2 { testB2 %Many :: Char }
+
+-- Fails because testA2 is partial
+test2 :: Test2 %1 -> Int
+test2 a = testA2 a
=====================================
testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr
=====================================
@@ -0,0 +1,10 @@
+LinearRecordSelectorFail.hs:11:7: error: [GHC-18872]
+ • Couldn't match type ‘Many’ with ‘One’
+ arising from multiplicity of ‘a’
+ • In an equation for ‘test1’: test1 a = testA11 a
+
+LinearRecordSelectorFail.hs:17:7: error: [GHC-18872]
+ • Couldn't match type ‘Many’ with ‘One’
+ arising from multiplicity of ‘a’
+ • In an equation for ‘test2’: test2 a = testA2 a
+
=====================================
testsuite/tests/linear/should_fail/all.T
=====================================
@@ -11,6 +11,7 @@ test('LinearNoExt', normal, compile_fail, [''])
test('LinearNoExtU', normal, compile_fail, [''])
test('LinearAsPat', normal, compile_fail, [''])
test('LinearLazyPat', normal, compile_fail, [''])
+test('LinearRecordSelectorFail', normal, compile_fail, [''])
test('LinearRecordUpdate', normal, compile_fail, [''])
test('LinearSeq', normal, compile_fail, [''])
test('LinearViewPattern', normal, compile_fail, [''])
=====================================
testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr
=====================================
@@ -1,4 +1,3 @@
-
DRFHoleFits.hs:7:7: error: [GHC-88464]
• Found hole: _ :: T -> Int
• In the expression: _ :: T -> Int
@@ -6,8 +5,10 @@ DRFHoleFits.hs:7:7: error: [GHC-88464]
• Relevant bindings include
bar :: T -> Int (bound at DRFHoleFits.hs:7:1)
Valid hole fits include
- foo :: T -> Int (defined at DRFHoleFits.hs:5:16)
bar :: T -> Int (defined at DRFHoleFits.hs:7:1)
+ foo :: T -> Int
+ with foo
+ (defined at DRFHoleFits.hs:5:16)
DRFHoleFits.hs:8:7: error: [GHC-88464]
• Found hole: _ :: A.S -> Int
@@ -18,5 +19,7 @@ DRFHoleFits.hs:8:7: error: [GHC-88464]
Valid hole fits include
baz :: A.S -> Int (defined at DRFHoleFits.hs:8:1)
A.foo :: A.S -> Int
+ with A.foo
(imported qualified from ‘DRFHoleFits_A’ at DRFHoleFits.hs:3:1-35
(and originally defined at DRFHoleFits_A.hs:5:16-18))
+
=====================================
testsuite/tests/overloadedrecflds/should_fail/T23063.stderr
=====================================
@@ -1,4 +1,3 @@
-
T23063.hs:5:7: error: [GHC-88464]
• Found hole: _ :: A.S -> Int
• In the expression: _ :: A.S -> Int
@@ -8,5 +7,7 @@ T23063.hs:5:7: error: [GHC-88464]
Valid hole fits include
baz :: A.S -> Int (defined at T23063.hs:5:1)
A.foo :: A.S -> Int
+ with A.foo
(imported qualified from ‘T23063_aux’ at T23063.hs:3:1-32
(and originally defined at T23063_aux.hs:4:16-18))
+
=====================================
testsuite/tests/overloadedrecflds/should_run/overloadedrecfldsrun04.stdout
=====================================
@@ -1,5 +1,8 @@
data Main.R = Main.MkR {Main.foo :: GHC.Internal.Types.Int}
-Main.foo :: Main.R -> GHC.Internal.Types.Int
-Main.foo :: Main.R -> GHC.Internal.Types.Int
-Main.foo :: Main.R -> GHC.Internal.Types.Int
+Main.foo :: forall {m_0 :: GHC.Internal.Types.Multiplicity} .
+ Main.R %m_0 -> GHC.Internal.Types.Int
+Main.foo :: forall {m_0 :: GHC.Internal.Types.Multiplicity} .
+ Main.R %m_0 -> GHC.Internal.Types.Int
+Main.foo :: forall {m_0 :: GHC.Internal.Types.Multiplicity} .
+ Main.R %m_0 -> GHC.Internal.Types.Int
42
=====================================
testsuite/tests/simplCore/should_compile/OpaqueNoCastWW.stderr
=====================================
@@ -1,22 +1,32 @@
==================== Tidy Core ====================
Result size of Tidy Core
- = {terms: 82, types: 52, coercions: 29, joins: 0/0}
+ = {terms: 83, types: 55, coercions: 31, joins: 0/0}
--- RHS size: {terms: 3, types: 3, coercions: 0, joins: 0/0}
-unsafeToInteger1 :: forall (n :: Nat). Signed n -> Signed n
+-- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0}
+unsafeToInteger1
+ :: forall (n :: Nat) (m :: GHC.Internal.Types.Multiplicity).
+ Signed n %m -> Signed n
[GblId, Arity=1, Unf=OtherCon []]
-unsafeToInteger1 = \ (@(n :: Nat)) (ds :: Signed n) -> ds
+unsafeToInteger1
+ = \ (@(n :: Nat))
+ (@(m :: GHC.Internal.Types.Multiplicity))
+ (ds :: Signed n) ->
+ ds
--- RHS size: {terms: 1, types: 0, coercions: 8, joins: 0/0}
-unsafeToInteger :: forall (n :: Nat). Signed n -> Integer
+-- RHS size: {terms: 1, types: 0, coercions: 10, joins: 0/0}
+unsafeToInteger
+ :: forall (n :: Nat) {m :: GHC.Internal.Types.Multiplicity}.
+ Signed n %m -> Integer
[GblId[[RecSel]], Arity=1, Unf=OtherCon []]
unsafeToInteger
= unsafeToInteger1
- `cast` (forall (n :: <Nat>_N).
- <Signed n>_R %<Many>_N ->_R OpaqueNoCastWW.N:Signed <n>_P
- :: (forall (n :: Nat). Signed n -> Signed n)
- ~R# (forall (n :: Nat). Signed n -> Integer))
+ `cast` (forall (n :: <Nat>_N) (m :: <GHC.Internal.Types.Multiplicity>_N).
+ <Signed n>_R %<m>_N ->_R OpaqueNoCastWW.N:Signed <n>_P
+ :: (forall (n :: Nat) (m :: GHC.Internal.Types.Multiplicity).
+ Signed n %m -> Signed n)
+ ~R# (forall (n :: Nat) (m :: GHC.Internal.Types.Multiplicity).
+ Signed n %m -> Integer))
-- RHS size: {terms: 8, types: 7, coercions: 21, joins: 0/0}
times [InlPrag=OPAQUE]
=====================================
testsuite/tests/typecheck/should_fail/CommonFieldTypeMismatch.stderr
=====================================
@@ -1,3 +1,11 @@
-CommonFieldTypeMismatch.hs:3:1: [GHC-91827]
- Constructors A1 and A2 give different types for field ‘fld’
- In the data type declaration for ‘A’
+CommonFieldTypeMismatch.hs:3:1: error: [GHC-91827]
+ • Constructors A1 and A2 give different types for field ‘fld’
+ • In the data type declaration for ‘A’
+
+CommonFieldTypeMismatch.hs:4:8: error: [GHC-83865]
+ • Couldn't match type ‘[Char]’ with ‘Int’
+ Expected: Int
+ Actual: String
+ • In the expression: fld
+ In an equation for ‘fld’: fld A2 {fld = fld} = fld
+
=====================================
utils/haddock/html-test/ref/Bug294.html
=====================================
@@ -159,9 +159,13 @@
><p class="src"
><a id="v:problemField" class="def"
>problemField</a
- > :: TO <a href="#" title="Bug294"
+ > :: <span class="keyword"
+ >forall</span
+ > {m :: <a href="#" title="GHC.Exts"
+ >Multiplicity</a
+ >}. TO <a href="#" title="Bug294"
>A</a
- > -> <a href="#" title="Bug294"
+ > %m -> <a href="#" title="Bug294"
>A</a
> <a href="#" class="selflink"
>#</a
@@ -171,9 +175,13 @@
><p class="src"
><a id="v:problemField-39-" class="def"
>problemField'</a
- > :: DO <a href="#" title="Bug294"
+ > :: <span class="keyword"
+ >forall</span
+ > {m :: <a href="#" title="GHC.Exts"
+ >Multiplicity</a
+ >}. DO <a href="#" title="Bug294"
>A</a
- > -> <a href="#" title="Bug294"
+ > %m -> <a href="#" title="Bug294"
>A</a
> <a href="#" class="selflink"
>#</a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/36658aeadc5679e73e9323ed1acca7…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/36658aeadc5679e73e9323ed1acca7…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T18570] 2 commits: Calculate multiplicity for record selector functions
by Sjoerd Visscher (@trac-sjoerd_visscher) 24 Jun '25
by Sjoerd Visscher (@trac-sjoerd_visscher) 24 Jun '25
24 Jun '25
Sjoerd Visscher pushed to branch wip/T18570 at Glasgow Haskell Compiler / GHC
Commits:
01c57b8f by Sjoerd Visscher at 2025-06-24T15:48:23+02:00
Calculate multiplicity for record selector functions
Until now record selector functions always had multiplicity Many, but when all the other fields have been declared with multiplicity Many (including the case when there are no other fields), then the selector function is allowed to be used linearly too, as it is allowed to discard all the other fields. Since in that case the multiplicity can be both One and Many, the selector function is made multiplicity-polymorphic.
- - - - -
36658aea by Sjoerd Visscher at 2025-06-24T15:48:32+02:00
Test
- - - - -
11 changed files:
- compiler/GHC/Core/DataCon.hs
- compiler/GHC/Tc/TyCl/PatSyn.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/bugs.rst
- docs/users_guide/exts/linear_types.rst
- + testsuite/tests/linear/should_compile/LinearRecordSelector.hs
- testsuite/tests/linear/should_compile/all.T
- + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs
- + testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr
- testsuite/tests/linear/should_fail/all.T
Changes:
=====================================
compiler/GHC/Core/DataCon.hs
=====================================
@@ -44,6 +44,7 @@ module GHC.Core.DataCon (
dataConInstOrigArgTys, dataConRepArgTys, dataConResRepTyArgs,
dataConInstUnivs,
dataConFieldLabels, dataConFieldType, dataConFieldType_maybe,
+ dataConOtherFieldsAllMultMany,
dataConSrcBangs,
dataConSourceArity, dataConVisArity, dataConRepArity,
dataConIsInfix,
@@ -1406,6 +1407,15 @@ dataConFieldType_maybe :: DataCon -> FieldLabelString
dataConFieldType_maybe con label
= find ((== label) . flLabel . fst) (dcFields con `zip` (scaledThing <$> dcOrigArgTys con))
+-- | Check if all the fields of the 'DataCon' have multiplicity 'Many',
+-- except for the given labelled field. In this case the selector
+-- of the given field can be a linear function, since it is allowed
+-- to discard all the other fields.
+dataConOtherFieldsAllMultMany :: DataCon -> FieldLabelString -> Bool
+dataConOtherFieldsAllMultMany con label
+ = all (\(fld, mult) -> flLabel fld == label || isManyTy mult)
+ (dcFields con `zip` (scaledMult <$> dcOrigArgTys con))
+
-- | Strictness/unpack annotations, from user; or, for imported
-- DataCons, from the interface file
-- The list is in one-to-one correspondence with the arity of the 'DataCon'
=====================================
compiler/GHC/Tc/TyCl/PatSyn.hs
=====================================
@@ -841,7 +841,7 @@ mkPatSynRecSelBinds :: PatSyn
-> FieldSelectors
-> [(Id, LHsBind GhcRn)]
mkPatSynRecSelBinds ps fields has_sel
- = [ mkOneRecordSelector [PatSynCon ps] (RecSelPatSyn ps) fld_lbl has_sel
+ = [ mkOneRecordSelector False [PatSynCon ps] (RecSelPatSyn ps) fld_lbl has_sel
| fld_lbl <- fields ]
isUnidirectional :: HsPatSynDir a -> Bool
=====================================
compiler/GHC/Tc/TyCl/Utils.hs
=====================================
@@ -32,7 +32,7 @@ import GHC.Tc.Utils.Env
import GHC.Tc.Gen.Bind( tcValBinds )
import GHC.Tc.Utils.TcType
-import GHC.Builtin.Types( unitTy )
+import GHC.Builtin.Types( unitTy, manyDataConTy, multiplicityTy )
import GHC.Builtin.Uniques ( mkBuiltinUnique )
import GHC.Hs
@@ -71,6 +71,7 @@ import GHC.Types.Name.Env
import GHC.Types.Name.Reader ( mkRdrUnqual )
import GHC.Types.Id
import GHC.Types.Id.Info
+import GHC.Types.Var (mkTyVar)
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Types.Unique.Set
@@ -765,7 +766,8 @@ addTyConsToGblEnv tyclss
do { traceTc "tcAddTyCons" $ vcat
[ text "tycons" <+> ppr tyclss
, text "implicits" <+> ppr implicit_things ]
- ; gbl_env <- tcRecSelBinds (mkRecSelBinds tyclss)
+ -- ; linearEnabled <- xoptM LangExt.LinearTypes
+ ; gbl_env <- tcRecSelBinds (mkRecSelBinds True tyclss)
; th_bndrs <- tcTyThBinders implicit_things
; return (gbl_env, th_bndrs)
}
@@ -848,24 +850,24 @@ tcRecSelBinds sel_bind_prs
, let loc = getSrcSpan sel_id ]
binds = [(NonRecursive, [bind]) | (_, bind) <- sel_bind_prs]
-mkRecSelBinds :: [TyCon] -> [(Id, LHsBind GhcRn)]
+mkRecSelBinds :: Bool -> [TyCon] -> [(Id, LHsBind GhcRn)]
-- NB We produce *un-typechecked* bindings, rather like 'deriving'
-- This makes life easier, because the later type checking will add
-- all necessary type abstractions and applications
-mkRecSelBinds tycons
- = map mkRecSelBind [ (tc,fld) | tc <- tycons
- , fld <- tyConFieldLabels tc ]
+mkRecSelBinds allowMultiplicity tycons
+ = [ mkRecSelBind allowMultiplicity tc fld | tc <- tycons
+ , fld <- tyConFieldLabels tc ]
-mkRecSelBind :: (TyCon, FieldLabel) -> (Id, LHsBind GhcRn)
-mkRecSelBind (tycon, fl)
- = mkOneRecordSelector all_cons (RecSelData tycon) fl
+mkRecSelBind :: Bool -> TyCon -> FieldLabel -> (Id, LHsBind GhcRn)
+mkRecSelBind allowMultiplicity tycon fl
+ = mkOneRecordSelector allowMultiplicity all_cons (RecSelData tycon) fl
FieldSelectors -- See Note [NoFieldSelectors and naughty record selectors]
where
all_cons = map RealDataCon (tyConDataCons tycon)
-mkOneRecordSelector :: [ConLike] -> RecSelParent -> FieldLabel -> FieldSelectors
+mkOneRecordSelector :: Bool -> [ConLike] -> RecSelParent -> FieldLabel -> FieldSelectors
-> (Id, LHsBind GhcRn)
-mkOneRecordSelector all_cons idDetails fl has_sel
+mkOneRecordSelector allowMultiplicity all_cons idDetails fl has_sel
= (sel_id, L (noAnnSrcSpan loc) sel_bind)
where
loc = getSrcSpan sel_name
@@ -916,17 +918,24 @@ mkOneRecordSelector all_cons idDetails fl has_sel
-- thus suppressing making a binding
-- A slight hack!
+ all_other_fields_unrestricted = all all_other_unrestricted all_cons
+ where
+ all_other_unrestricted PatSynCon{} = False
+ all_other_unrestricted (RealDataCon dc) = dataConOtherFieldsAllMultMany dc lbl
+
sel_ty | is_naughty = unitTy -- See Note [Naughty record selectors]
- | otherwise = mkForAllTys sel_tvbs $
+ | otherwise = mkForAllTys (sel_tvbs ++ mult_tvb) $
-- Urgh! See Note [The stupid context] in GHC.Core.DataCon
- mkPhiTy (conLikeStupidTheta con1) $
+ mkPhiTy (conLikeStupidTheta con1) $
-- req_theta is empty for normal DataCon
- mkPhiTy req_theta $
- mkVisFunTyMany data_ty $
- -- Record selectors are always typed with Many. We
- -- could improve on it in the case where all the
- -- fields in all the constructor have multiplicity Many.
+ mkPhiTy req_theta $
+ mkVisFunTy sel_mult data_ty $
field_ty
+ non_partial = length all_cons == length cons_w_field -- See Note [Multiplicity and partial selectors]
+ (mult_tvb, sel_mult) = if allowMultiplicity && non_partial && all_other_fields_unrestricted
+ then ([mkForAllTyBinder (Invisible InferredSpec) mult_var], mkTyVarTy mult_var)
+ else ([], manyDataConTy)
+ mult_var = mkTyVar (mkSysTvName (mkBuiltinUnique 1) (fsLit "m")) multiplicityTy
-- make the binding: sel (C2 { fld = x }) = x
-- sel (C7 { fld = x }) = x
@@ -1165,4 +1174,13 @@ Therefore, when used in the right-hand side of `unT`, GHC attempts to
instantiate `a` with `(forall b. b -> b) -> Int`, which is impredicative.
To make sure that GHC is OK with this, we enable ImpredicativeTypes internally
when typechecking these HsBinds so that the user does not have to.
+
+Note [Multiplicity and partial selectors]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+While all logic for making record selectors multiplicity-polymorphic also applies
+to partial selectors, there is a technical difficulty: the catch-all default case
+that is added throws away its argument, and so cannot be linear. A simple workaround
+was not found. There may exist a more complicated workaround, but the combination of
+linear types and partial selectors is not expected to be very popular in practice, so
+it was decided to not allow multiplicity-polymorphic partial selectors at all.
-}
=====================================
docs/users_guide/9.14.1-notes.rst
=====================================
@@ -67,6 +67,13 @@ Language
This causes the constructor to have type ``Rec :: Int %'Many -> Char %1 -> Record``.
+ Also record selector functions are now multiplicity-polymorphic when possible.
+ In the above example the selector function ``y`` now has type
+ ``y :: Record %m -> Char``, because the ``x`` field is allowed to be discarded.
+ In particular this always applies to the selector of a newtype wrapper.
+ (Note that in theory this should also work with partial record selectors,
+ but for technical reasons this is not supported.)
+
* The :extension:`ExplicitNamespaces` extension now allows the ``data``
namespace specifier in import and export lists.
=====================================
docs/users_guide/bugs.rst
=====================================
@@ -701,6 +701,9 @@ Bugs in GHC
- Because of a toolchain limitation we are unable to support full Unicode paths
on Windows. On Windows we support up to Latin-1. See :ghc-ticket:`12971` for more.
+- For technical reasons, partial record selectors cannot be made
+ multiplicity-polymorphic, so they are always unrestricted.
+
.. _bugs-ghci:
Bugs in GHCi (the interactive GHC)
=====================================
docs/users_guide/exts/linear_types.rst
=====================================
@@ -238,7 +238,7 @@ to use ``MkT1`` in higher order functions. The additional multiplicity
argument ``m`` is marked as inferred (see
:ref:`inferred-vs-specified`), so that there is no conflict with
visible type application. When displaying types, unless
-``-XLinearTypes`` is enabled, multiplicity polymorphic functions are
+``-XLinearTypes`` is enabled, multiplicity-polymorphic functions are
printed as regular functions (see :ref:`printing-linear-types`);
therefore constructors appear to have regular function types.
@@ -256,21 +256,33 @@ using GADT syntax or record syntax. Given
::
data T2 a b c where
- MkT2 :: a -> b %1 -> c %1 -> T2 a b c -- Note unrestricted arrow in the first argument
+ MkT2 :: a -> b %1 -> c -> T2 a b c -- Note the unrestricted arrows on a and c
-the value ``MkT2 x y z`` can be constructed only if ``x`` is
-unrestricted. On the other hand, a linear function which is matching
-on ``MkT2 x y z`` must consume ``y`` and ``z`` exactly once, but there
-is no restriction on ``x``. The same example can be written using record syntax:
+the value ``MkT2 x y z`` can be constructed only if ``x`` and
+``z`` are unrestricted. On the other hand, a linear function which is
+matching on ``MkT2 x y z`` must consume ``y`` exactly once, but there
+is no restriction on ``x`` and ``z``.
+The same example can be written using record syntax:
::
- data T2 a b c = MkT2 { x %'Many :: a, y :: b, z :: c }
+ data T2 a b c = MkT2 { x %'Many :: a, y :: b, z %'Many :: c }
Again, the constructor ``MkT2`` has type ``MkT2 :: a -> b %1 -> c %1 -> T2 a b c``.
Note that by default record fields are linear, only unrestricted fields
-require a multiplicity annotation. The annotation has no effect on the record selectors.
-So ``x`` has type ``x :: T2 a b c -> a`` and similarly ``y`` has type ``y :: T2 a b c -> b``.
+require a multiplicity annotation.
+
+The multiplicity of record selectors is inferred from the multiplicity of the fields. Note that
+the effect of a selector is to discard all the other fields, so it can only be linear if all the
+other fields are unrestricted. So ``x`` has type ``x :: T2 a b c -> a``, because the ``y`` field
+is not unrestricted. But the ``x`` and ``z`` fields are unrestricted, so the selector for ``y``
+can be linear, and therefore it is made to be multiplicity-polymorphic: ``y :: T2 a b c %m -> b``.
+In particular this always applies to the selector of a newtype wrapper.
+
+In the case of multiple constructors, this logic is repeated for each constructor. So a selector
+is only made multiplicity-polymorphic if for every constructor all the other fields are unrestricted.
+(For technical reasons, partial record selectors cannot be made multiplicity-polymorphic, so they
+are always unrestricted.)
It is also possible to define a multiplicity-polymorphic field:
=====================================
testsuite/tests/linear/should_compile/LinearRecordSelector.hs
=====================================
@@ -0,0 +1,21 @@
+{-# LANGUAGE LinearTypes, DataKinds, OverloadedRecordDot, RebindableSyntax #-}
+module LinearRecordSelector where
+
+import GHC.Exts (Multiplicity(..))
+import Prelude
+
+data Test = A { test :: Int, test2 %Many :: String } | B { test %Many :: Int, test3 %Many :: Char }
+
+test1 :: Test %1 -> Int
+test1 a = test a
+
+testM :: Test -> Int
+testM a = test a
+
+testX :: Test %m -> Int
+testX = test
+
+newtype NT = NT { unNT :: Int }
+
+nt :: NT %m -> Int
+nt a = unNT a
=====================================
testsuite/tests/linear/should_compile/all.T
=====================================
@@ -36,6 +36,7 @@ test('LinearTH3', normal, compile, [''])
test('LinearTH4', req_th, compile, [''])
test('LinearHole', normal, compile, [''])
test('LinearDataConSections', normal, compile, [''])
+test('LinearRecordSelector', normal, compile, ['-dcore-lint'])
test('T18731', normal, compile, [''])
test('T19400', unless(compiler_debugged(), skip), compile, [''])
test('T20023', normal, compile, [''])
=====================================
testsuite/tests/linear/should_fail/LinearRecordSelectorFail.hs
=====================================
@@ -0,0 +1,17 @@
+{-# LANGUAGE LinearTypes, DataKinds, OverloadedRecordDot, RebindableSyntax #-}
+module LinearRecordSelector where
+
+import GHC.Exts (Multiplicity(..))
+import Prelude
+
+data Test1 = A1 { testA11 :: Int, testA12 :: String }
+
+-- Fails because testA12 is linear
+test1 :: Test1 %1 -> Int
+test1 a = testA11 a
+
+data Test2 = A2 { testA2 :: Int } | B2 { testB2 %Many :: Char }
+
+-- Fails because testA2 is partial
+test2 :: Test2 %1 -> Int
+test2 a = testA2 a
=====================================
testsuite/tests/linear/should_fail/LinearRecordSelectorFail.stderr
=====================================
@@ -0,0 +1,10 @@
+LinearRecordSelectorFail.hs:14:7: error: [GHC-18872]
+ • Couldn't match type ‘Many’ with ‘One’
+ arising from multiplicity of ‘a’
+ • In an equation for ‘test1’: test1 a = testA11 a
+
+LinearRecordSelectorFail.hs:20:7: error: [GHC-18872]
+ • Couldn't match type ‘Many’ with ‘One’
+ arising from multiplicity of ‘a’
+ • In an equation for ‘test2’: test2 a = testA2 a
+
=====================================
testsuite/tests/linear/should_fail/all.T
=====================================
@@ -11,6 +11,7 @@ test('LinearNoExt', normal, compile_fail, [''])
test('LinearNoExtU', normal, compile_fail, [''])
test('LinearAsPat', normal, compile_fail, [''])
test('LinearLazyPat', normal, compile_fail, [''])
+test('LinearRecordSelectorFail', normal, compile_fail, [''])
test('LinearRecordUpdate', normal, compile_fail, [''])
test('LinearSeq', normal, compile_fail, [''])
test('LinearViewPattern', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/430288ea63c2c022eceb5649199520…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/430288ea63c2c022eceb5649199520…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/teo/allow-newer-ghc-paths] 12 commits: Visible forall in GADTs (#25127)
by Teo Camarasu (@teo) 24 Jun '25
by Teo Camarasu (@teo) 24 Jun '25
24 Jun '25
Teo Camarasu pushed to branch wip/teo/allow-newer-ghc-paths at Glasgow Haskell Compiler / GHC
Commits:
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.
- - - - -
878c3888 by Teo Camarasu at 2025-06-24T13:46:32+00:00
cabal.project-reinstall: allow newer ghc-paths:Cabal
This upper bound will be wrong whenever we are using a development version of Cabal in-tree, so let's just add an allow-newer here
- - - - -
112 changed files:
- cabal.project-reinstall
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.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/Make.hs
- compiler/GHC/Core/Opt/Pipeline.hs
- compiler/GHC/Core/PatSyn.hs
- compiler/GHC/Core/TyCo/Ppr.hs
- compiler/GHC/Core/TyCo/Rep.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Env.hs
- compiler/GHC/Driver/Env/Types.hs
- compiler/GHC/Driver/Main.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/Hs/Pat.hs
- compiler/GHC/Hs/Type.hs
- compiler/GHC/HsToCore/Errors/Ppr.hs
- compiler/GHC/HsToCore/Errors/Types.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/Iface/Decl.hs
- compiler/GHC/Iface/Ext/Ast.hs
- compiler/GHC/Iface/Load.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/PostProcess/Haddock.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.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/Instance/Family.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Build.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Id/Make.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/Language/Haskell/Syntax/Decls.hs
- compiler/Language/Haskell/Syntax/Pat.hs
- distrib/configure.ac.in
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/gadt_syntax.rst
- docs/users_guide/exts/required_type_arguments.rst
- ghc/GHCi/UI.hs
- hadrian/cfg/default.host.target.in
- hadrian/cfg/default.target.in
- hadrian/cfg/system.config.in
- hadrian/src/Builder.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Settings/Builders/RunTest.hs
- libraries/ghc-boot-th/GHC/Boot/TH/Ppr.hs
- linters/lint-whitespace/lint-whitespace.cabal
- m4/fp_settings.m4
- m4/ghc_toolchain.m4
- m4/prep_target_file.m4
- rts/linker/LoadArchive.c
- testsuite/tests/dependent/should_fail/T16326_Fail6.stderr
- 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/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T15323.stderr
- testsuite/tests/printer/T18791.stderr
- + 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/T20868.stdout
- testsuite/tests/th/all.T
- testsuite/tests/typecheck/should_compile/T23739a.hs
- + testsuite/tests/typecheck/should_compile/TyAppPat_Tricky.hs
- testsuite/tests/typecheck/should_compile/all.T
- testsuite/tests/typecheck/should_fail/T20443b.stderr
- testsuite/tests/typecheck/should_fail/TyAppPat_TooMany.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/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
- utils/check-exact/ExactPrint.hs
- utils/ghc-toolchain/exe/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Target.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/GhcUtils.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bec4067da0a7a8a00cf26d468a8710…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bec4067da0a7a8a00cf26d468a8710…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/fendor/no-load] Implement `-ghci-no-load` flag
by Hannes Siebenhandl (@fendor) 24 Jun '25
by Hannes Siebenhandl (@fendor) 24 Jun '25
24 Jun '25
Hannes Siebenhandl pushed to branch wip/fendor/no-load at Glasgow Haskell Compiler / GHC
Commits:
101b61fd by fendor at 2025-06-24T15:37:36+02:00
Implement `-ghci-no-load` flag
We add the new flag `-ghci-no-load` 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
`-ghci-no-load` flag.
The `-ghci-no-load` 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`.
- - - - -
33 changed files:
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Unit/Module/Graph.hs
- docs/users_guide/ghci.rst
- ghc/GHCi/UI.hs
- + 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/prog021/all.T
- − testsuite/tests/ghci/prog021/prog021.T
- testsuite/tests/ghci/prog021/prog021.script → testsuite/tests/ghci/prog021/prog021a.script
- testsuite/tests/ghci/prog021/prog021.stderr → testsuite/tests/ghci/prog021/prog021a.stderr
- testsuite/tests/ghci/prog021/prog021.stdout → 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
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/101b61fdd265571cc244d66be930fad…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/101b61fdd265571cc244d66be930fad…
You're receiving this email because of your account on gitlab.haskell.org.
1
0