Simon Peyton Jones pushed new branch wip/T26015 at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T26015
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Serge S. Gulin pushed to branch wip/T25974 at Glasgow Haskell Compiler / GHC
Commits:
4631de44 by Serge S. Gulin at 2025-05-06T11:26:23+03:00
Add Wine support
- - - - -
8 changed files:
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- boot
- configure.ac
- hadrian/src/Builder.hs
- hadrian/src/Rules/BinaryDist.hs
- libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
- m4/find_merge_objects.m4
Changes:
=====================================
.gitlab/ci.sh
=====================================
@@ -75,6 +75,15 @@ Environment variables affecting both build systems:
NIX_SYSTEM On Darwin, the target platform of the desired toolchain
(either "x86-64-darwin" or "aarch-darwin")
NO_BOOT Whether to run ./boot or not, used when testing the source dist
+ TOOLCHAIN_SOURCE Select a source of toolchain. Possible values:
+ - "env": Toolchains are included in the Docker image via environment
+ variables. Default for Linux.
+ - "nix": Toolchains are provided via .gitlab/darwin/toolchain.nix.
+ Default for Darwin.
+ - "extracted":
+ Toolchains will be downloaded and extracted through the
+ CI process. Default for other systems. Windows and FreeBSD
+ are included.
Environment variables determining build configuration of Hadrian system:
@@ -83,14 +92,14 @@ Environment variables determining build configuration of Hadrian system:
This tests the "reinstall" configuration
CROSS_EMULATOR The emulator to use for testing of cross-compilers.
-Environment variables determining bootstrap toolchain (Linux):
+Environment variables determining bootstrap toolchain (TOOLCHAIN_SOURCE=env):
GHC Path of GHC executable to use for bootstrapping.
CABAL Path of cabal-install executable to use for bootstrapping.
ALEX Path of alex executable to use for bootstrapping.
HAPPY Path of alex executable to use for bootstrapping.
-Environment variables determining bootstrap toolchain (non-Linux):
+Environment variables determining bootstrap toolchain (TOOLCHAIN_SOURCE=extracted):
GHC_VERSION Which GHC version to fetch for bootstrapping.
CABAL_INSTALL_VERSION
@@ -132,10 +141,33 @@ function setup_locale() {
}
function mingw_init() {
+ if [[ "${TOOLCHAIN_SOURCE:-}" =~ "env" ]]; then
+ # We assume that passed GHC will be used as a bootstrap ghc compiler
+ if [ -n "${GHC:-}" ]; then
+ boot_triple=$($GHC --info | awk -F'"' '/Target platform/ {print $4}')
+ else
+ boot_triple=$(ghc --info | awk -F'"' '/Target platform/ {print $4}')
+ fi
+ else
+ case "$MSYSTEM" in
+ CLANG64)
+ boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC
+ ;;
+ CLANGARM64)
+ boot_triple="aarch64-unknown-mingw32" # triple of bootstrap GHC
+ ;;
+ *)
+ fail "win32-init: Unknown MSYSTEM $MSYSTEM"
+ ;;
+ esac
+ fi
+
case "$MSYSTEM" in
CLANG64)
target_triple="x86_64-unknown-mingw32"
- boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC
+ ;;
+ CLANGARM64)
+ target_triple="aarch64-unknown-mingw32"
;;
*)
fail "win32-init: Unknown MSYSTEM $MSYSTEM"
@@ -150,10 +182,19 @@ function mingw_init() {
MINGW_MOUNT_POINT="${MINGW_PREFIX}"
PATH="$MINGW_MOUNT_POINT/bin:$PATH"
- # We always use mingw64 Python to avoid path length issues like #17483.
- export PYTHON="/mingw64/bin/python3"
- # And need to use sphinx-build from the environment
- export SPHINXBUILD="/mingw64/bin/sphinx-build.exe"
+ case "$MSYSTEM" in
+ CLANGARM64)
+ # At MSYS for ARM64 we force to use their special versions to speedup the compiler step
+ export PYTHON="/clangarm64/bin/python3"
+ export SPHINXBUILD="/clangarm64/bin/sphinx-build.exe"
+ ;;
+ *)
+ # We always use mingw64 Python to avoid path length issues like #17483.
+ export PYTHON="/mingw64/bin/python3"
+ # And need to use sphinx-build from the environment
+ export SPHINXBUILD="/mingw64/bin/sphinx-build.exe"
+ ;;
+ esac
}
# This will contain GHC's local native toolchain
@@ -178,15 +219,21 @@ function show_tool() {
}
function set_toolchain_paths() {
- case "$(uname -m)-$(uname)" in
- # Linux toolchains are included in the Docker image
- *-Linux) toolchain_source="env" ;;
- # Darwin toolchains are provided via .gitlab/darwin/toolchain.nix
- *-Darwin) toolchain_source="nix" ;;
- *) toolchain_source="extracted" ;;
- esac
+ if [ -z "${TOOLCHAIN_SOURCE:-}" ]
+ then
+ # Fallback to automatic detection which could not work for cases
+ # when cross compiler will be build at Windows environment
+ # and requires a special mingw compiler (not bundled)
+ case "$(uname -m)-$(uname)" in
+ # Linux toolchains are included in the Docker image
+ *-Linux) TOOLCHAIN_SOURCE="env" ;;
+ # Darwin toolchains are provided via .gitlab/darwin/toolchain.nix
+ *-Darwin) TOOLCHAIN_SOURCE="nix" ;;
+ *) TOOLCHAIN_SOURCE="extracted" ;;
+ esac
+ fi
- case "$toolchain_source" in
+ case "$TOOLCHAIN_SOURCE" in
extracted)
# These are populated by setup_toolchain
GHC="$toolchain/bin/ghc$exe"
@@ -217,7 +264,7 @@ function set_toolchain_paths() {
: ${HAPPY:=$(which happy)}
: ${ALEX:=$(which alex)}
;;
- *) fail "bad toolchain_source"
+ *) fail "bad TOOLCHAIN_SOURCE"
esac
export GHC
@@ -247,7 +294,7 @@ function setup() {
cp -Rf "$CABAL_CACHE"/* "$CABAL_DIR"
fi
- case $toolchain_source in
+ case $TOOLCHAIN_SOURCE in
extracted) time_it "setup" setup_toolchain ;;
*) ;;
esac
@@ -405,6 +452,17 @@ function configure() {
if [[ -n "${target_triple:-}" ]]; then
args+=("--target=$target_triple")
fi
+ if [[ "${TOOLCHAIN_SOURCE:-}" =~ "extracted" ]]; then
+ # To extract something need download something first.
+ args+=("--enable-tarballs-autodownload")
+ else
+ # For Windows we should explicitly --enable-distro-toolchain
+ # if i.e. we decided to use TOOLCHAIN_SOURCE = env
+ case "$(uname)" in
+ MSYS_*|MINGW*) args+=("--enable-distro-toolchain") ;;
+ *) ;;
+ esac
+ fi
if [[ -n "${ENABLE_NUMA:-}" ]]; then
args+=("--enable-numa")
else
@@ -421,7 +479,6 @@ function configure() {
# See https://stackoverflow.com/questions/7577052 for a rationale for the
# args[@] symbol-soup below.
run ${CONFIGURE_WRAPPER:-} ./configure \
- --enable-tarballs-autodownload \
"${args[@]+"${args[@]}"}" \
GHC="$GHC" \
|| ( cat config.log; fail "configure failed" )
@@ -562,12 +619,14 @@ function install_bindist() {
read -r -a args <<< "${INSTALL_CONFIGURE_ARGS:-}"
if [[ "${CROSS_TARGET:-no_cross_target}" =~ "mingw" ]]; then
- # We suppose that host target = build target.
+ # We assume that BUILD=HOST.
# By the fact above it is clearly turning out which host value is
# for currently built compiler.
# The fix for #21970 will probably remove this if-branch.
- local -r CROSS_HOST_GUESS=$($SHELL ./config.guess)
- args+=( "--target=$CROSS_TARGET" "--host=$CROSS_HOST_GUESS" )
+ # Cut is needed due of See Note [Wide Triple Windows].
+ # By default it guesses "(x86_64|aarch64)-w64-mingw32"
+ local -r CROSS_HOST_ARCH_GUESS=$($SHELL ./config.guess | cut -d'-' -f1)
+ args+=( "--target=$CROSS_TARGET" "--host=$CROSS_HOST_ARCH_GUESS-unknown-mingw32" )
# FIXME: The bindist configure script shouldn't need to be reminded of
# the target platform. See #21970.
=====================================
.gitlab/generate-ci/gen_ci.hs
=====================================
@@ -1302,11 +1302,14 @@ cross_jobs = [
. setVariable "WindresCmd" (llvm_prefix ++ "windres")
. setVariable "LLVMAS" (llvm_prefix ++ "clang")
. setVariable "LD" (llvm_prefix ++ "ld")
+ -- See Note [Empty MergeObjsCmd]
-- Windows target require to make linker merge feature check disabled.
. setVariable "MergeObjsCmd" ""
+ -- Note [Wide Triple Windows]
+ -- ~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- LLVM MinGW Linux Toolchain expects to recieve "aarch64-w64-mingw32"
-- as a triple but we use more common "aarch64-unknown-mingw32".
- -- Due of this we need configure ld manually for clang beacause
+ -- Due of this we need configure ld manually for clang because
-- it will use system's ld otherwise when --target will be specified to
-- unexpected triple.
. setVariable "CFLAGS" cflags
=====================================
boot
=====================================
@@ -52,6 +52,8 @@ def autoreconf():
# Run autoreconf on everything that needs it.
processes = {}
if os.name == 'nt':
+ # Note [ACLOCAL_PATH for Windows]
+ # ~~~~~~~~~~~~~~~~~~~~~~~~~
# Get the normalized ACLOCAL_PATH for Windows
# This is necessary since on Windows this will be a Windows
# path, which autoreconf doesn't know doesn't know how to handle.
=====================================
configure.ac
=====================================
@@ -658,12 +658,13 @@ GHC_LLVM_TARGET_SET_VAR
AC_SUBST(LlvmTarget)
dnl ** See whether cc supports --target=<triple> and set
-dnl CONF_CC_OPTS_STAGE[012] accordingly.
-FP_CC_SUPPORTS_TARGET([$CC_STAGE0], [CONF_CC_OPTS_STAGE0], [CONF_CXX_OPTS_STAGE0])
+dnl CONF_CC_OPTS_STAGE[12] accordingly.
FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1])
FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_CXX_OPTS_STAGE2])
-FP_PROG_CC_LINKER_TARGET([$CC_STAGE0], [CONF_CC_OPTS_STAGE0], [CONF_GCC_LINKER_OPTS_STAGE0])
+# CONF_CC_OPTS_STAGE0 should be left as is because it is already configured
+# by bootstrap compiler settings
+
FP_PROG_CC_LINKER_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_GCC_LINKER_OPTS_STAGE1])
FP_PROG_CC_LINKER_TARGET([$CC], [CONF_CC_OPTS_STAGE2], [CONF_GCC_LINKER_OPTS_STAGE2])
=====================================
hadrian/src/Builder.hs
=====================================
@@ -26,7 +26,7 @@ import Hadrian.Builder.Tar
import Hadrian.Oracles.Path
import Hadrian.Oracles.TextFile
import Hadrian.Utilities
-import Oracles.Setting (bashPath, targetStage)
+import Oracles.Setting (bashPath, targetStage, isWinHost)
import System.Exit
import System.IO (stderr)
@@ -327,8 +327,14 @@ instance H.Builder Builder where
Ar Unpack _ -> cmd' [Cwd output] [path] buildArgs buildOptions
Autoreconf dir -> do
+ isWin <- isWinHost
+ let aclocal_env =
+ -- It is generally assumed that you would use MinGW's compilers from within an MSYS shell.
+ -- See Note [ACLOCAL_PATH for Windows]
+ if isWin then [AddEnv "ACLOCAL_PATH" "/c/msys64/usr/share/aclocal/"]
+ else []
bash <- bashPath
- cmd' [Cwd dir] [bash, path] buildArgs buildOptions
+ cmd' (Cwd dir `cons` aclocal_env) [bash, path] buildArgs buildOptions
Configure dir -> do
-- Inject /bin/bash into `libtool`, instead of /bin/sh,
=====================================
hadrian/src/Rules/BinaryDist.hs
=====================================
@@ -115,7 +115,12 @@ installTo relocatable prefix = do
targetPlatform <- setting TargetPlatformFull
let ghcVersionPretty = "ghc-" ++ version ++ "-" ++ targetPlatform
bindistFilesDir = root -/- "bindist" -/- ghcVersionPretty
- runBuilder (Configure bindistFilesDir) ["--prefix="++prefix] [] []
+ win <- isWinTarget
+ -- See Note [Empty MergeObjsCmd]
+ let disabledMerge =
+ if win then ["MergeObjsCmd="]
+ else []
+ runBuilder (Configure bindistFilesDir) (["--prefix="++prefix] ++ disabledMerge) [] []
let env = case relocatable of
Relocatable -> [AddEnv "RelocatableBuild" "YES"]
NotRelocatable -> []
@@ -232,7 +237,7 @@ bindistRules = do
-- N.B. the ghc-pkg executable may be prefixed with a target triple
-- (c.f. #20267).
ghcPkgName <- programName (vanillaContext Stage1 ghcPkg)
- cmd_ (bindistFilesDir -/- "bin" -/- ghcPkgName) ["recache"]
+ cmd_ (bindistFilesDir -/- "bin" -/- ghcPkgName <.> exe) ["recache"]
=====================================
libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
=====================================
@@ -861,7 +861,9 @@ expirationTime mgr us = do
-- The 'TimeoutCallback' will not be called more than once.
--
-- Be careful not to exceed @maxBound :: Int@, which on 32-bit machines is only
--- 2147483647 μs, less than 36 minutes.
+-- 2147483647 microseconds, less than 36 minutes.
+-- We can not use here utf/greek symbol due of:
+-- _build/stage1/libraries/ghc-internal/build/GHC/Internal/Event/Windows.hs: commitBuffer: invalid argument (cannot encode character '\206')
--
{-# NOINLINE registerTimeout #-}
registerTimeout :: Manager -> Int -> TimeoutCallback -> IO TimeoutKey
@@ -878,7 +880,9 @@ registerTimeout mgr@Manager{..} uSrelTime cb = do
-- This has no effect if the timeout has already fired.
--
-- Be careful not to exceed @maxBound :: Int@, which on 32-bit machines is only
--- 2147483647 μs, less than 36 minutes.
+-- 2147483647 microseconds, less than 36 minutes.
+-- We can not use here utf/greek symbol due of:
+-- _build/stage1/libraries/ghc-internal/build/GHC/Internal/Event/Windows.hs: commitBuffer: invalid argument (cannot encode character '\206')
--
updateTimeout :: Manager -> TimeoutKey -> Seconds -> IO ()
updateTimeout mgr (TK key) relTime = do
@@ -980,7 +984,7 @@ step maxDelay mgr@Manager{..} = do
-- There are some unusual edge cases you need to deal with. The
-- GetQueuedCompletionStatus function blocks a thread until there's
-- work for it to do. Based on the return value, the number of bytes
- -- and the overlapped structure, there’s a lot of possible "reasons"
+ -- and the overlapped structure, there's a lot of possible "reasons"
-- for the function to have returned. Deciphering all the possible
-- cases:
--
=====================================
m4/find_merge_objects.m4
=====================================
@@ -33,6 +33,8 @@ AC_DEFUN([FIND_MERGE_OBJECTS],[
fi
+ # Note [Empty MergeObjsCmd]
+ # ~~~~~~~~~~~~~~~~~~~~~~~~~
# If MergeObjsCmd="" then we assume that the user is explicitly telling us that
# they do not want to configure the MergeObjsCmd, this is particularly important for
# the bundled windows toolchain.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4631de44afcc6e9ee839623a61c1051…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4631de44afcc6e9ee839623a61c1051…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Suppress unused do-binding if discarded variable is Any or ZonkAny.
by Marge Bot (@marge-bot) 06 May '25
by Marge Bot (@marge-bot) 06 May '25
06 May '25
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
50fa8165 by Javran Cheng at 2025-05-05T05:55:39-04:00
Suppress unused do-binding if discarded variable is Any or ZonkAny.
Consider example (#25895):
> do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`.
Nothing constrains `b`, so it will be instantiates with `Any` or
`ZonkAny`.
But we certainly don't want to complain about a discarded do-binding.
Fixes #25895
- - - - -
fa47b3f9 by Rodrigo Mesquita at 2025-05-06T04:21:37-04:00
Refactor mkTopLevImportedEnv out of mkTopLevEnv
This makes the code clearer and allows the top-level import context to
be fetched directly from the HomeModInfo through the API (e.g. useful
for the debugger).
- - - - -
e8dadf65 by Rodrigo Mesquita at 2025-05-06T04:21:37-04:00
Export sizeOccEnv from GHC.Types.Name.Occurrence
Counts the number of OccNames in an OccEnv
- - - - -
85fc3ef8 by Simon Peyton Jones at 2025-05-06T04:21:38-04:00
Fix a bad untouchability bug im simplifyInfer
This patch addresses #26004. The root cause was that simplifyInfer
was willing to unify variables "far out". The fix, in
runTcSWithEvBinds', is to initialise the inert set given-eq level with
the current level. See
(TGE6) in Note [Tracking Given equalities]
in GHC.Tc.Solver.InertSet
Two loosely related refactors:
* Refactored approximateWCX to return just the free type
variables of the un-quantified constraints. That avoids duplication
of work (these free vars are needed in simplifyInfer) and makes it
clearer that the constraints themselves are irrelevant.
* A little local refactor of TcSMode, which reduces the number of
parameters to runTcSWithEvBinds
- - - - -
15 changed files:
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Types/Name/Occurrence.hs
- testsuite/tests/printer/T17697.stderr
- + testsuite/tests/typecheck/should_fail/T26004.hs
- + testsuite/tests/typecheck/should_fail/T26004.stderr
- testsuite/tests/typecheck/should_fail/T7453.stderr
- testsuite/tests/typecheck/should_fail/all.T
Changes:
=====================================
compiler/GHC/Builtin/Types.hs
=====================================
@@ -510,6 +510,17 @@ Wrinkles:
See examples in ghc-prim:GHC.Types
+(Any8) Warning about unused bindings of type `Any` and `ZonkAny` are suppressed,
+ following the same rationale of supressing warning about the unit type.
+
+ For example, consider (#25895):
+
+ do { forever (return ()); blah }
+
+ where forever :: forall a b. IO a -> IO b
+ Nothing constrains `b`, so it will be instantiates with `Any` or `ZonkAny`.
+ But we certainly don't want to complain about a discarded do-binding.
+
The Any tycon used to be quite magic, but we have since been able to
implement it merely with an empty kind polymorphic type family. See #10886 for a
bit of history.
=====================================
compiler/GHC/HsToCore/Expr.hs
=====================================
@@ -1243,9 +1243,13 @@ warnDiscardedDoBindings rhs m_ty elt_ty
; when (warn_unused || warn_wrong) $
do { fam_inst_envs <- dsGetFamInstEnvs
; let norm_elt_ty = topNormaliseType fam_inst_envs elt_ty
-
- -- Warn about discarding non-() things in 'monadic' binding
- ; if warn_unused && not (isUnitTy norm_elt_ty)
+ supressible_ty =
+ isUnitTy norm_elt_ty || isAnyTy norm_elt_ty || isZonkAnyTy norm_elt_ty
+ -- Warn about discarding things in 'monadic' binding,
+ -- however few types are excluded:
+ -- * Unit type `()`
+ -- * `ZonkAny` or `Any` type see (Any8) of Note [Any types]
+ ; if warn_unused && not supressible_ty
then diagnosticDs (DsUnusedDoBind rhs elt_ty)
else
=====================================
compiler/GHC/HsToCore/Pmc/Solver/Types.hs
=====================================
@@ -64,7 +64,7 @@ import GHC.Builtin.Names
import GHC.Builtin.Types
import GHC.Builtin.Types.Prim
import GHC.Tc.Solver.InertSet (InertSet, emptyInert)
-import GHC.Tc.Utils.TcType (isStringTy)
+import GHC.Tc.Utils.TcType (isStringTy, topTcLevel)
import GHC.Types.CompleteMatch
import GHC.Types.SourceText (SourceText(..), mkFractionalLit, FractionalLit
, fractionalLitFromRational
@@ -129,7 +129,7 @@ instance Outputable TyState where
ppr (TySt n inert) = ppr n <+> ppr inert
initTyState :: TyState
-initTyState = TySt 0 emptyInert
+initTyState = TySt 0 (emptyInert topTcLevel)
-- | The term oracle state. Stores 'VarInfo' for encountered 'Id's. These
-- entries are possibly shared when we figure out that two variables must be
=====================================
compiler/GHC/Runtime/Eval.hs
=====================================
@@ -23,7 +23,7 @@ module GHC.Runtime.Eval (
setupBreakpoint,
back, forward,
setContext, getContext,
- mkTopLevEnv,
+ mkTopLevEnv, mkTopLevImportedEnv,
getNamesInScope,
getRdrNamesInScope,
moduleIsInterpreted,
@@ -836,29 +836,36 @@ mkTopLevEnv hsc_env modl
Nothing -> pure $ Left "not a home module"
Just details ->
case mi_top_env (hm_iface details) of
- (IfaceTopEnv exports imports) -> do
- imports_env <-
- runInteractiveHsc hsc_env
- $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env
- $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv)
- $ forM imports $ \iface_import -> do
- let ImpUserSpec spec details = tcIfaceImport iface_import
- iface <- loadInterfaceForModule (text "imported by GHCi") (is_mod spec)
- pure $ case details of
- ImpUserAll -> importsFromIface hsc_env iface spec Nothing
- ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns)
- ImpUserExplicit x _parents_of_implicits ->
- -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y).
- -- It is only used for error messages. It seems dubious even to add an import context to these GREs as
- -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that
- -- the test case produce the same output as before.
- let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } }
- in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x
+ (IfaceTopEnv exports _imports) -> do
+ imports_env <- mkTopLevImportedEnv hsc_env details
let exports_env = mkGlobalRdrEnv $ gresFromAvails hsc_env Nothing (getDetOrdAvails exports)
pure $ Right $ plusGlobalRdrEnv imports_env exports_env
where
hpt = hsc_HPT hsc_env
+-- | Make the top-level environment with all bindings imported by this module.
+-- Exported bindings from this module are not included in the result.
+mkTopLevImportedEnv :: HscEnv -> HomeModInfo -> IO GlobalRdrEnv
+mkTopLevImportedEnv hsc_env details = do
+ runInteractiveHsc hsc_env
+ $ ioMsgMaybe $ hoistTcRnMessage $ runTcInteractive hsc_env
+ $ fmap (foldr plusGlobalRdrEnv emptyGlobalRdrEnv)
+ $ forM imports $ \iface_import -> do
+ let ImpUserSpec spec details = tcIfaceImport iface_import
+ iface <- loadInterfaceForModule (text "imported by GHCi") (is_mod spec)
+ pure $ case details of
+ ImpUserAll -> importsFromIface hsc_env iface spec Nothing
+ ImpUserEverythingBut ns -> importsFromIface hsc_env iface spec (Just ns)
+ ImpUserExplicit x _parents_of_implicits ->
+ -- TODO: Not quite right, is_explicit should refer to whether the user wrote A(..) or A(x,y).
+ -- It is only used for error messages. It seems dubious even to add an import context to these GREs as
+ -- they are not "imported" into the top-level scope of the REPL. I changed this for now so that
+ -- the test case produce the same output as before.
+ let spec' = ImpSpec { is_decl = spec, is_item = ImpSome { is_explicit = True, is_iloc = noSrcSpan } }
+ in mkGlobalRdrEnv $ gresFromAvails hsc_env (Just spec') x
+ where
+ IfaceTopEnv _ imports = mi_top_env (hm_iface details)
+
-- | Get the interactive evaluation context, consisting of a pair of the
-- set of modules from which we take the full top-level scope, and the set
-- of modules from which we take just the exports respectively.
=====================================
compiler/GHC/Tc/Solver.hs
=====================================
@@ -915,21 +915,22 @@ simplifyInfer top_lvl rhs_tclvl infer_mode sigs name_taus wanteds
; let psig_theta = concatMap sig_inst_theta partial_sigs
-- First do full-blown solving
- -- NB: we must gather up all the bindings from doing
- -- this solving; hence (runTcSWithEvBinds ev_binds_var).
- -- And note that since there are nested implications,
- -- calling solveWanteds will side-effect their evidence
- -- bindings, so we can't just revert to the input
- -- constraint.
-
+ -- NB: we must gather up all the bindings from doing this solving; hence
+ -- (runTcSWithEvBinds ev_binds_var). And note that since there are
+ -- nested implications, calling solveWanteds will side-effect their
+ -- evidence bindings, so we can't just revert to the input constraint.
+ --
+ -- See also Note [Inferring principal types]
; ev_binds_var <- TcM.newTcEvBinds
; psig_evs <- newWanteds AnnOrigin psig_theta
; wanted_transformed
- <- setTcLevel rhs_tclvl $
- runTcSWithEvBinds ev_binds_var $
+ <- runTcSWithEvBinds ev_binds_var $
+ setTcLevelTcS rhs_tclvl $
solveWanteds (mkSimpleWC psig_evs `andWC` wanteds)
+ -- setLevelTcS: we do setLevel /inside/ the runTcS, so that
+ -- we initialise the InertSet inert_given_eq_lvl as far
+ -- out as possible, maximising oppportunities to unify
-- psig_evs : see Note [Add signature contexts as wanteds]
- -- See Note [Inferring principal types]
-- Find quant_pred_candidates, the predicates that
-- we'll consider quantifying over
@@ -1430,13 +1431,15 @@ decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
-- Step 1 of Note [decideAndPromoteTyVars]
-- Get candidate constraints, decide which we can potentially quantify
- (can_quant_cts, no_quant_cts) = approximateWCX wanted
+ -- The `no_quant_tvs` are free in constraints we can't quantify.
+ (can_quant_cts, no_quant_tvs) = approximateWCX False wanted
can_quant = ctsPreds can_quant_cts
- no_quant = ctsPreds no_quant_cts
+ can_quant_tvs = tyCoVarsOfTypes can_quant
-- Step 2 of Note [decideAndPromoteTyVars]
-- Apply the monomorphism restriction
(post_mr_quant, mr_no_quant) = applyMR dflags infer_mode can_quant
+ mr_no_quant_tvs = tyCoVarsOfTypes mr_no_quant
-- The co_var_tvs are tvs mentioned in the types of covars or
-- coercion holes. We can't quantify over these covars, so we
@@ -1448,30 +1451,33 @@ decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
++ tau_tys ++ post_mr_quant)
co_var_tvs = closeOverKinds co_vars
- -- outer_tvs are mentioned in `wanted, and belong to some outer level.
+ -- outer_tvs are mentioned in `wanted`, and belong to some outer level.
-- We definitely can't quantify over them
outer_tvs = outerLevelTyVars rhs_tclvl $
- tyCoVarsOfTypes can_quant `unionVarSet` tyCoVarsOfTypes no_quant
+ can_quant_tvs `unionVarSet` no_quant_tvs
- -- Step 3 of Note [decideAndPromoteTyVars]
+ -- Step 3 of Note [decideAndPromoteTyVars], (a-c)
-- Identify mono_tvs: the type variables that we must not quantify over
+ -- At top level we are much less keen to create mono tyvars, to avoid
+ -- spooky action at a distance.
mono_tvs_without_mr
- | is_top_level = outer_tvs
- | otherwise = outer_tvs -- (a)
- `unionVarSet` tyCoVarsOfTypes no_quant -- (b)
- `unionVarSet` co_var_tvs -- (c)
+ | is_top_level = outer_tvs -- See (DP2)
+ | otherwise = outer_tvs -- (a)
+ `unionVarSet` no_quant_tvs -- (b)
+ `unionVarSet` co_var_tvs -- (c)
+ -- Step 3 of Note [decideAndPromoteTyVars], (d)
mono_tvs_with_mr
= -- Even at top level, we don't quantify over type variables
-- mentioned in constraints that the MR tells us not to quantify
-- See Note [decideAndPromoteTyVars] (DP2)
- mono_tvs_without_mr `unionVarSet` tyCoVarsOfTypes mr_no_quant
+ mono_tvs_without_mr `unionVarSet` mr_no_quant_tvs
--------------------------------------------------------------------
-- Step 4 of Note [decideAndPromoteTyVars]
-- Use closeWrtFunDeps to find any other variables that are determined by mono_tvs
- add_determined tvs = closeWrtFunDeps post_mr_quant tvs
- `delVarSetList` psig_qtvs
+ add_determined tvs preds = closeWrtFunDeps preds tvs
+ `delVarSetList` psig_qtvs
-- Why delVarSetList psig_qtvs?
-- If the user has explicitly asked for quantification, then that
-- request "wins" over the MR.
@@ -1480,8 +1486,8 @@ decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
-- (i.e. says "no" to isQuantifiableTv)? That's OK: explanation
-- in Step 2 of Note [Deciding quantification].
- mono_tvs_with_mr_det = add_determined mono_tvs_with_mr
- mono_tvs_without_mr_det = add_determined mono_tvs_without_mr
+ mono_tvs_with_mr_det = add_determined mono_tvs_with_mr post_mr_quant
+ mono_tvs_without_mr_det = add_determined mono_tvs_without_mr can_quant
--------------------------------------------------------------------
-- Step 5 of Note [decideAndPromoteTyVars]
@@ -1518,7 +1524,7 @@ decideAndPromoteTyVars top_lvl rhs_tclvl infer_mode name_taus psigs wanted
, text "newly_mono_tvs =" <+> ppr newly_mono_tvs
, text "can_quant =" <+> ppr can_quant
, text "post_mr_quant =" <+> ppr post_mr_quant
- , text "no_quant =" <+> ppr no_quant
+ , text "no_quant_tvs =" <+> ppr no_quant_tvs
, text "mr_no_quant =" <+> ppr mr_no_quant
, text "final_quant =" <+> ppr final_quant
, text "co_vars =" <+> ppr co_vars ]
@@ -1605,8 +1611,8 @@ The plan
The body of z tries to unify the type of x (call it alpha[1]) with
(beta[2] -> gamma[2]). This unification fails because alpha is untouchable, leaving
[W] alpha[1] ~ (beta[2] -> gamma[2])
- We need to know not to quantify over beta or gamma, because they are in the
- equality constraint with alpha. Actual test case: typecheck/should_compile/tc213
+ We don't want to quantify over beta or gamma because they are fixed by alpha,
+ which is monomorphic. Actual test case: typecheck/should_compile/tc213
Another example. Suppose we have
class C a b | a -> b
@@ -1643,9 +1649,22 @@ Wrinkles
promote type variables. But for bindings affected by the MR we have no choice
but to promote.
+ An example is in #26004.
+ f w e = case e of
+ T1 -> let y = not w in False
+ T2 -> True
+ When generalising `f` we have a constraint
+ forall. (a ~ Bool) => alpha ~ Bool
+ where our provisional type for `f` is `f :: T alpha -> blah`.
+ In a /nested/ setting, we might simply not-generalise `f`, hoping to learn
+ about `alpha` from f's call sites (test T5266b is an example). But at top
+ level, to avoid spooky action at a distance.
+
Note [The top-level Any principle]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Key principle: we never want to show the programmer a type with `Any` in it.
+Key principles:
+ * we never want to show the programmer a type with `Any` in it.
+ * avoid "spooky action at a distance" and silent defaulting
Most /top level/ bindings have a type signature, so none of this arises. But
where a top-level binding lacks a signature, we don't want to infer a type like
@@ -1654,11 +1673,18 @@ and then subsequently default alpha[0]:=Any. Exposing `Any` to the user is bad
bad bad. Better to report an error, which is what may well happen if we
quantify over alpha instead.
+Moreover,
+ * If (elsewhere in this module) we add a call to `f`, say (f True), then
+ `f` will get the type `Bool -> Int`
+ * If we add /another/ call, say (f 'x'), we will then get a type error.
+ * If we have no calls, the final exported type of `f` may get set by
+ defaulting, and might not be principal (#26004).
+
For /nested/ bindings, a monomorphic type like `f :: alpha[0] -> Int` is fine,
because we can see all the call sites of `f`, and they will probably fix
`alpha`. In contrast, we can't see all of (or perhaps any of) the calls of
top-level (exported) functions, reducing the worries about "spooky action at a
-distance".
+distance". This also moves in the direction of `MonoLocalBinds`, which we like.
Note [Do not quantify over constraints that determine a variable]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
=====================================
compiler/GHC/Tc/Solver/InertSet.hs
=====================================
@@ -374,20 +374,20 @@ instance Outputable InertSet where
where
dicts = bagToList (dictsToBag solved_dicts)
-emptyInertCans :: InertCans
-emptyInertCans
+emptyInertCans :: TcLevel -> InertCans
+emptyInertCans given_eq_lvl
= IC { inert_eqs = emptyTyEqs
, inert_funeqs = emptyFunEqs
- , inert_given_eq_lvl = topTcLevel
+ , inert_given_eq_lvl = given_eq_lvl
, inert_given_eqs = False
, inert_dicts = emptyDictMap
, inert_safehask = emptyDictMap
, inert_insts = []
, inert_irreds = emptyBag }
-emptyInert :: InertSet
-emptyInert
- = IS { inert_cans = emptyInertCans
+emptyInert :: TcLevel -> InertSet
+emptyInert given_eq_lvl
+ = IS { inert_cans = emptyInertCans given_eq_lvl
, inert_cycle_breakers = emptyBag :| []
, inert_famapp_cache = emptyFunEqs
, inert_solved_dicts = emptyDictMap }
@@ -678,6 +678,23 @@ should update inert_given_eq_lvl?
imply nominal ones. For example, if (G a ~R G b) and G's argument's
role is nominal, then we can deduce a ~N b.
+(TGE6) A subtle point is this: when initialising the solver, giving it
+ an empty InertSet, we must conservatively initialise `inert_given_lvl`
+ to the /current/ TcLevel. This matters when doing let-generalisation.
+ Consider #26004:
+ f w e = case e of
+ T1 -> let y = not w in False -- T1 is a GADT
+ T2 -> True
+ When let-generalising `y`, we will have (w :: alpha[1]) in the type
+ envt; and we are under GADT pattern match. So when we solve the
+ constraints from y's RHS, in simplifyInfer, we must NOT unify
+ alpha[1] := Bool
+ Since we don't know what enclosing equalities there are, we just
+ conservatively assume that there are some.
+
+ This initialisation in done in `runTcSWithEvBinds`, which passes
+ the current TcLevl to `emptyInert`.
+
Historical note: prior to #24938 we also ignored Given equalities that
did not mention an "outer" type variable. But that is wrong, as #24938
showed. Another example is immortalised in test LocalGivenEqs2
=====================================
compiler/GHC/Tc/Solver/Monad.hs
=====================================
@@ -20,7 +20,7 @@ module GHC.Tc.Solver.Monad (
runTcSSpecPrag,
failTcS, warnTcS, addErrTcS, wrapTcS, ctLocWarnTcS,
runTcSEqualities,
- nestTcS, nestImplicTcS, setEvBindsTcS,
+ nestTcS, nestImplicTcS, setEvBindsTcS, setTcLevelTcS,
emitImplicationTcS, emitTvImplicationTcS,
emitImplication,
emitFunDepWanteds,
@@ -947,8 +947,9 @@ added. This is initialised from the innermost implication constraint.
-- | See Note [TcSMode]
data TcSMode
= TcSVanilla -- ^ Normal constraint solving
+ | TcSPMCheck -- ^ Used when doing patterm match overlap checks
| TcSEarlyAbort -- ^ Abort early on insoluble constraints
- | TcSSpecPrag -- ^ Fully solve all constraints
+ | TcSSpecPrag -- ^ Fully solve all constraints
deriving (Eq)
{- Note [TcSMode]
@@ -957,6 +958,11 @@ The constraint solver can operate in different modes:
* TcSVanilla: Normal constraint solving mode. This is the default.
+* TcSPMCheck: Used by the pattern match overlap checker.
+ Like TcSVanilla, but the idea is that the returned InertSet will
+ later be resumed, so we do not want to restore type-equality cycles
+ See also Note [Type equality cycles] in GHC.Tc.Solver.Equality
+
* TcSEarlyAbort: Abort (fail in the monad) as soon as we come across an
insoluble constraint. This is used to fail-fast when checking for hole-fits.
See Note [Speeding up valid hole-fits].
@@ -1135,7 +1141,7 @@ runTcS tcs
runTcSEarlyAbort :: TcS a -> TcM a
runTcSEarlyAbort tcs
= do { ev_binds_var <- TcM.newTcEvBinds
- ; runTcSWithEvBinds' True TcSEarlyAbort ev_binds_var tcs }
+ ; runTcSWithEvBinds' TcSEarlyAbort ev_binds_var tcs }
-- | Run the 'TcS' monad in 'TcSSpecPrag' mode, which either fully solves
-- individual Wanted quantified constraints or leaves them alone.
@@ -1143,7 +1149,7 @@ runTcSEarlyAbort tcs
-- See Note [TcSSpecPrag].
runTcSSpecPrag :: EvBindsVar -> TcS a -> TcM a
runTcSSpecPrag ev_binds_var tcs
- = runTcSWithEvBinds' True TcSSpecPrag ev_binds_var tcs
+ = runTcSWithEvBinds' TcSSpecPrag ev_binds_var tcs
{- Note [TcSSpecPrag]
~~~~~~~~~~~~~~~~~~~~~
@@ -1200,7 +1206,7 @@ runTcSEqualities thing_inside
runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet)
runTcSInerts inerts tcs = do
ev_binds_var <- TcM.newTcEvBinds
- runTcSWithEvBinds' False TcSVanilla ev_binds_var $ do
+ runTcSWithEvBinds' TcSPMCheck ev_binds_var $ do
setInertSet inerts
a <- tcs
new_inerts <- getInertSet
@@ -1209,21 +1215,23 @@ runTcSInerts inerts tcs = do
runTcSWithEvBinds :: EvBindsVar
-> TcS a
-> TcM a
-runTcSWithEvBinds = runTcSWithEvBinds' True TcSVanilla
+runTcSWithEvBinds = runTcSWithEvBinds' TcSVanilla
-runTcSWithEvBinds' :: Bool -- True <=> restore type equality cycles
- -- Don't if you want to reuse the InertSet.
- -- See also Note [Type equality cycles]
- -- in GHC.Tc.Solver.Equality
- -> TcSMode
+runTcSWithEvBinds' :: TcSMode
-> EvBindsVar
-> TcS a
-> TcM a
-runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs
+runTcSWithEvBinds' mode ev_binds_var tcs
= do { unified_var <- TcM.newTcRef 0
- ; step_count <- TcM.newTcRef 0
- ; inert_var <- TcM.newTcRef emptyInert
- ; wl_var <- TcM.newTcRef emptyWorkList
+ ; step_count <- TcM.newTcRef 0
+
+ -- Make a fresh, empty inert set
+ -- Subtle point: see (TGE6) in Note [Tracking Given equalities]
+ -- in GHC.Tc.Solver.InertSet
+ ; tc_lvl <- TcM.getTcLevel
+ ; inert_var <- TcM.newTcRef (emptyInert tc_lvl)
+
+ ; wl_var <- TcM.newTcRef emptyWorkList
; unif_lvl_var <- TcM.newTcRef Nothing
; let env = TcSEnv { tcs_ev_binds = ev_binds_var
, tcs_unified = unified_var
@@ -1240,9 +1248,13 @@ runTcSWithEvBinds' restore_cycles mode ev_binds_var tcs
; when (count > 0) $
csTraceTcM $ return (text "Constraint solver steps =" <+> int count)
- ; when restore_cycles $
- do { inert_set <- TcM.readTcRef inert_var
- ; restoreTyVarCycles inert_set }
+ -- Restore tyvar cycles: see Note [Type equality cycles] in
+ -- GHC.Tc.Solver.Equality
+ -- But /not/ in TCsPMCheck mode: see Note [TcSMode]
+ ; case mode of
+ TcSPMCheck -> return ()
+ _ -> do { inert_set <- TcM.readTcRef inert_var
+ ; restoreTyVarCycles inert_set }
#if defined(DEBUG)
; ev_binds <- TcM.getTcEvBindsMap ev_binds_var
@@ -1284,6 +1296,10 @@ setEvBindsTcS :: EvBindsVar -> TcS a -> TcS a
setEvBindsTcS ref (TcS thing_inside)
= TcS $ \ env -> thing_inside (env { tcs_ev_binds = ref })
+setTcLevelTcS :: TcLevel -> TcS a -> TcS a
+setTcLevelTcS lvl (TcS thing_inside)
+ = TcS $ \ env -> TcM.setTcLevel lvl (thing_inside env)
+
nestImplicTcS :: EvBindsVar
-> TcLevel -> TcS a
-> TcS a
=====================================
compiler/GHC/Tc/Types/Constraint.hs
=====================================
@@ -1743,24 +1743,21 @@ will be able to report a more informative error:
************************************************************************
-}
-type ApproxWC = ( Bag Ct -- Free quantifiable constraints
- , Bag Ct ) -- Free non-quantifiable constraints
- -- due to shape, or enclosing equality
+type ApproxWC = ( Bag Ct -- Free quantifiable constraints
+ , TcTyCoVarSet ) -- Free vars of non-quantifiable constraints
+ -- due to shape, or enclosing equality
approximateWC :: Bool -> WantedConstraints -> Bag Ct
approximateWC include_non_quantifiable cts
- | include_non_quantifiable = quant `unionBags` no_quant
- | otherwise = quant
- where
- (quant, no_quant) = approximateWCX cts
+ = fst (approximateWCX include_non_quantifiable cts)
-approximateWCX :: WantedConstraints -> ApproxWC
+approximateWCX :: Bool -> WantedConstraints -> ApproxWC
-- The "X" means "extended";
-- we return both quantifiable and non-quantifiable constraints
-- See Note [ApproximateWC]
-- See Note [floatKindEqualities vs approximateWC]
-approximateWCX wc
- = float_wc False emptyVarSet wc (emptyBag, emptyBag)
+approximateWCX include_non_quantifiable wc
+ = float_wc False emptyVarSet wc (emptyBag, emptyVarSet)
where
float_wc :: Bool -- True <=> there are enclosing equalities
-> TcTyCoVarSet -- Enclosing skolem binders
@@ -1786,17 +1783,23 @@ approximateWCX wc
-- There can be (insoluble) Given constraints in wc_simple,
-- there so that we get error reports for unreachable code
-- See `given_insols` in GHC.Tc.Solver.Solve.solveImplication
- | insolubleCt ct = acc
- | tyCoVarsOfCt ct `intersectsVarSet` skol_tvs = acc
- | otherwise
- = case classifyPredType (ctPred ct) of
+ | insolubleCt ct = acc
+ | pred_tvs `intersectsVarSet` skol_tvs = acc
+ | include_non_quantifiable = add_to_quant
+ | is_quantifiable encl_eqs (ctPred ct) = add_to_quant
+ | otherwise = add_to_no_quant
+ where
+ pred = ctPred ct
+ pred_tvs = tyCoVarsOfType pred
+ add_to_quant = (ct `consBag` quant, no_quant)
+ add_to_no_quant = (quant, no_quant `unionVarSet` pred_tvs)
+
+ is_quantifiable encl_eqs pred
+ = case classifyPredType pred of
-- See the classification in Note [ApproximateWC]
EqPred eq_rel ty1 ty2
- | not encl_eqs -- See Wrinkle (W1)
- , quantify_equality eq_rel ty1 ty2
- -> add_to_quant
- | otherwise
- -> add_to_no_quant
+ | encl_eqs -> False -- encl_eqs: See Wrinkle (W1)
+ | otherwise -> quantify_equality eq_rel ty1 ty2
ClassPred cls tys
| Just {} <- isCallStackPred cls tys
@@ -1804,17 +1807,14 @@ approximateWCX wc
-- the constraints bubble up to be solved from the outer
-- context, or be defaulted when we reach the top-level.
-- See Note [Overview of implicit CallStacks] in GHC.Tc.Types.Evidence
- -> add_to_no_quant
+ -> False
| otherwise
- -> add_to_quant -- See Wrinkle (W2)
+ -> True -- See Wrinkle (W2)
- IrredPred {} -> add_to_quant -- See Wrinkle (W2)
+ IrredPred {} -> True -- See Wrinkle (W2)
- ForAllPred {} -> add_to_no_quant -- Never quantify these
- where
- add_to_quant = (ct `consBag` quant, no_quant)
- add_to_no_quant = (quant, ct `consBag` no_quant)
+ ForAllPred {} -> False -- Never quantify these
-- See Note [Quantifying over equality constraints]
quantify_equality NomEq ty1 ty2 = quant_fun ty1 || quant_fun ty2
@@ -1852,7 +1852,7 @@ We proceed by classifying the constraint:
Wrinkle (W1)
When inferring most-general types (in simplifyInfer), we
- do *not* float an equality constraint if the implication binds
+ do *not* quantify over equality constraint if the implication binds
equality constraints, because that defeats the OutsideIn story.
Consider data T a where { TInt :: T Int; MkT :: T a }
f TInt = 3::Int
=====================================
compiler/GHC/Tc/Utils/TcType.hs
=====================================
@@ -88,7 +88,7 @@ module GHC.Tc.Utils.TcType (
isSigmaTy, isRhoTy, isRhoExpTy, isOverloadedTy,
isFloatingPrimTy, isDoubleTy, isFloatTy, isIntTy, isWordTy, isStringTy,
isIntegerTy, isNaturalTy,
- isBoolTy, isUnitTy, isCharTy,
+ isBoolTy, isUnitTy, isAnyTy, isZonkAnyTy, isCharTy,
isTauTy, isTauTyCon, tcIsTyVarTy,
isPredTy, isTyVarClassPred,
checkValidClsArgs, hasTyVarHead,
@@ -2006,7 +2006,7 @@ isFloatTy, isDoubleTy,
isFloatPrimTy, isDoublePrimTy,
isIntegerTy, isNaturalTy,
isIntTy, isWordTy, isBoolTy,
- isUnitTy, isCharTy :: Type -> Bool
+ isUnitTy, isAnyTy, isZonkAnyTy, isCharTy :: Type -> Bool
isFloatTy = is_tc floatTyConKey
isDoubleTy = is_tc doubleTyConKey
isFloatPrimTy = is_tc floatPrimTyConKey
@@ -2017,6 +2017,8 @@ isIntTy = is_tc intTyConKey
isWordTy = is_tc wordTyConKey
isBoolTy = is_tc boolTyConKey
isUnitTy = is_tc unitTyConKey
+isAnyTy = is_tc anyTyConKey
+isZonkAnyTy = is_tc zonkAnyTyConKey
isCharTy = is_tc charTyConKey
-- | Check whether the type is of the form @Any :: k@,
=====================================
compiler/GHC/Types/Name/Occurrence.hs
=====================================
@@ -92,6 +92,7 @@ module GHC.Types.Name.Occurrence (
plusOccEnv, plusOccEnv_C,
extendOccEnv_Acc, filterOccEnv, delListFromOccEnv, delFromOccEnv,
alterOccEnv, minusOccEnv, minusOccEnv_C, minusOccEnv_C_Ns,
+ sizeOccEnv,
pprOccEnv, forceOccEnv,
intersectOccEnv_C,
@@ -803,6 +804,10 @@ minusOccEnv_C_Ns f (MkOccEnv as) (MkOccEnv bs) =
then Nothing
else Just m
+sizeOccEnv :: OccEnv a -> Int
+sizeOccEnv (MkOccEnv as) =
+ nonDetStrictFoldUFM (\ m !acc -> acc + sizeUFM m) 0 as
+
instance Outputable a => Outputable (OccEnv a) where
ppr x = pprOccEnv ppr x
=====================================
testsuite/tests/printer/T17697.stderr
=====================================
@@ -1,8 +1,2 @@
T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)]
Variable not in scope: threadDelay :: t0 -> IO a0
-
-T17697.hs:6:5: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
- A do-notation statement discarded a result of type
- ‘GHC.Internal.Types.ZonkAny 1’
- Suggested fix: Suppress this warning by saying ‘_ <- threadDelay 1’
-
=====================================
testsuite/tests/typecheck/should_fail/T26004.hs
=====================================
@@ -0,0 +1,14 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE NoMonoLocalBinds #-}
+
+module T26004 where
+
+data T a where
+ T1 :: T Bool
+ T2 :: T a
+
+-- This funcion should be rejected:
+-- we should not infer a non-principal type for `f`
+f w e = case e of
+ T1 -> let y = not w in False
+ T2 -> True
=====================================
testsuite/tests/typecheck/should_fail/T26004.stderr
=====================================
@@ -0,0 +1,17 @@
+
+T26004.hs:13:21: error: [GHC-25897]
+ • Could not deduce ‘p ~ Bool’
+ from the context: a ~ Bool
+ bound by a pattern with constructor: T1 :: T Bool,
+ in a case alternative
+ at T26004.hs:13:3-4
+ ‘p’ is a rigid type variable bound by
+ the inferred type of f :: p -> T a -> Bool
+ at T26004.hs:(12,1)-(14,12)
+ • In the first argument of ‘not’, namely ‘w’
+ In the expression: not w
+ In an equation for ‘y’: y = not w
+ • Relevant bindings include
+ w :: p (bound at T26004.hs:12:3)
+ f :: p -> T a -> Bool (bound at T26004.hs:12:1)
+ Suggested fix: Consider giving ‘f’ a type signature
=====================================
testsuite/tests/typecheck/should_fail/T7453.stderr
=====================================
@@ -1,8 +1,5 @@
-
-T7453.hs:9:15: error: [GHC-25897]
- • Couldn't match type ‘t’ with ‘p’
- Expected: Id t
- Actual: Id p
+T7453.hs:10:30: error: [GHC-25897]
+ • Couldn't match expected type ‘t’ with actual type ‘p’
‘t’ is a rigid type variable bound by
the type signature for:
z :: forall t. Id t
@@ -10,29 +7,17 @@ T7453.hs:9:15: error: [GHC-25897]
‘p’ is a rigid type variable bound by
the inferred type of cast1 :: p -> a
at T7453.hs:(7,1)-(10,30)
- • In the expression: aux
- In an equation for ‘z’:
- z = aux
- where
- aux = Id v
- In an equation for ‘cast1’:
- cast1 v
- = runId z
- where
- z :: Id t
- z = aux
- where
- aux = Id v
+ • In the first argument of ‘Id’, namely ‘v’
+ In the expression: Id v
+ In an equation for ‘aux’: aux = Id v
• Relevant bindings include
- aux :: Id p (bound at T7453.hs:10:21)
+ aux :: Id t (bound at T7453.hs:10:21)
z :: Id t (bound at T7453.hs:9:11)
v :: p (bound at T7453.hs:7:7)
cast1 :: p -> a (bound at T7453.hs:7:1)
-T7453.hs:15:15: error: [GHC-25897]
- • Couldn't match type ‘t1’ with ‘p’
- Expected: () -> t1
- Actual: () -> p
+T7453.hs:16:33: error: [GHC-25897]
+ • Couldn't match expected type ‘t1’ with actual type ‘p’
‘t1’ is a rigid type variable bound by
the type signature for:
z :: forall t1. () -> t1
@@ -40,21 +25,11 @@ T7453.hs:15:15: error: [GHC-25897]
‘p’ is a rigid type variable bound by
the inferred type of cast2 :: p -> t
at T7453.hs:(13,1)-(16,33)
- • In the expression: aux
- In an equation for ‘z’:
- z = aux
- where
- aux = const v
- In an equation for ‘cast2’:
- cast2 v
- = z ()
- where
- z :: () -> t
- z = aux
- where
- aux = const v
+ • In the first argument of ‘const’, namely ‘v’
+ In the expression: const v
+ In an equation for ‘aux’: aux = const v
• Relevant bindings include
- aux :: forall {b}. b -> p (bound at T7453.hs:16:21)
+ aux :: b -> t1 (bound at T7453.hs:16:21)
z :: () -> t1 (bound at T7453.hs:15:11)
v :: p (bound at T7453.hs:13:7)
cast2 :: p -> t (bound at T7453.hs:13:1)
@@ -86,3 +61,4 @@ T7453.hs:21:15: error: [GHC-25897]
z :: t1 (bound at T7453.hs:21:11)
v :: p (bound at T7453.hs:19:7)
cast3 :: p -> t (bound at T7453.hs:19:1)
+
=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -735,3 +735,4 @@ test('T24938', normal, compile_fail, [''])
test('T25325', normal, compile_fail, [''])
test('T25004', normal, compile_fail, [''])
test('T25004k', normal, compile_fail, [''])
+test('T26004', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1c4ddd212bd3dc24b8c8f46247f7f…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1c4ddd212bd3dc24b8c8f46247f7f…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/spj-apporv-Oct24] 14 commits: Support for ARM64 Windows (LLVM-enabled) (fixes #24603)
by Apoorv Ingle (@ani) 06 May '25
by Apoorv Ingle (@ani) 06 May '25
06 May '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
9995c2b7 by Serge S. Gulin at 2025-05-04T17:13:36+03:00
Support for ARM64 Windows (LLVM-enabled) (fixes #24603)
1. Add Windows AArch64 cross-compilation support via CI jobs
Introduce new CI configurations for cross-compiling to Windows ARM64 using Debian12Wine, FEX, and MSYS2.
Configure toolchain variables for LLVM MinGW and Wine emulation in CI pipelines.
2. Adjust compiler and RTS for AArch64 Windows compatibility
Reserve register `x18` on Windows and Darwin platforms in AArch64 codegen.
Handle Windows-specific relocations and data sections in AArch64 assembler.
Update PEi386 linker to recognize ARM64 binaries and support exception handling.
Adjust LLVM target definitions and data layouts for new architectures.
Update `ghc-toolchain` and build scripts to handle `TablesNextToCode` on Windows ARM64.
3. Enhance CI scripts and stability
Modify `ci.sh` to handle mingw cross-targets, fixing GHC executable paths and test execution.
Use `diff -w` in tests to ignore whitespace differences, improving cross-platform consistency.
4. Refactor and clean up code
Remove redundant imports in hello.hs test.
Improve error messages and checks for unsupported configurations in the driver.
Add `EXDEV` error code to `errno.js`.
Add async/sync flags to IO logs at `base.js`.
Improve POSIX compatibility for file close at `base.js`: decrease indeterminism for mixed cases of async and sync code.
5. Update dependencies: `Cabal`, `Win32`, `directory`, `process`, `haskeline`, and `unix`.
submodule
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
Co-authored-by: Dmitrii Egorov <egorov.d.i(a)icloud.com>
Co-authored-by: Andrei Borzenkov <root(a)sandwitch.dev>
- - - - -
50fa8165 by Javran Cheng at 2025-05-05T05:55:39-04:00
Suppress unused do-binding if discarded variable is Any or ZonkAny.
Consider example (#25895):
> do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`.
Nothing constrains `b`, so it will be instantiates with `Any` or
`ZonkAny`.
But we certainly don't want to complain about a discarded do-binding.
Fixes #25895
- - - - -
27705207 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
- Remove one `SrcSpan` field from `VAExpansion`. It is no longer needed.
- Make `tcExpr` take a `Maybe HsThingRn` which will be passed on to tcApp and used by splitHsApps to determine a more accurate `AppCtx`
- `tcXExpr` is less hacky now
- do not look through HsExpansion applications
- kill OrigPat and remove HsThingRn From VAExpansion
- look through XExpr ExpandedThingRn while inferring type of head
- always set in generated code after stepping inside a ExpandedThingRn
- fixing record update error messages
- remove special case of tcbody from tcLambdaMatches
- wrap last stmt expansion in a HsPar so that the error messages are prettier
- remove special case of dsExpr for ExpandedThingTc
- make EExpand (HsExpr GhcRn) instead of EExpand HsThingRn
- fixing error messages for rebindable
- - - - -
e1ba0c2c by Apoorv Ingle at 2025-05-05T20:23:00-05:00
some progress on tick
- - - - -
3e146809 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
remove adhoc cases from ticks
- - - - -
41a42e55 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
fix the case where head of the application chain is an expanded expression and the argument is a type application c.f. T19167.hs
- - - - -
cc46e9c6 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
move setQLInstLevel inside tcInstFun
- - - - -
a8a9edda by Apoorv Ingle at 2025-05-05T20:23:00-05:00
ignore ds warnings originating from gen locations
- - - - -
c0c01891 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
filter expr stmts error msgs
- - - - -
486cee8b by Apoorv Ingle at 2025-05-05T20:23:00-05:00
exception for AppDo while making error ctxt
- - - - -
7dcd5b45 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
moving around things for locations and error ctxts
- - - - -
6c4e8559 by Apoorv Ingle at 2025-05-05T20:23:00-05:00
popErrCtxt doesn't push contexts and popErrCtxts in the first argument to bind and >> in do expansion statements
- - - - -
f1936171 by Apoorv Ingle at 2025-05-05T20:24:45-05:00
accept test cases with changed error messages
-------------------------
Metric Decrease:
T9020
-------------------------
- - - - -
4dc324fd by Apoorv Ingle at 2025-05-05T20:24:54-05:00
look through PopErrCtxt while splitting exprs in application chains
- - - - -
77 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/hello.hs
- .gitlab/jobs.yaml
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/Expr.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Match.hs
- compiler/GHC/HsToCore/Pmc.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Ticks.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Gen/App.hs
- + compiler/GHC/Tc/Gen/App.hs-boot
- compiler/GHC/Tc/Gen/Do.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcType.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/BinaryDist.hs
- libraries/Cabal
- libraries/Win32
- libraries/base/src/System/CPUTime/Windows.hsc
- libraries/base/tests/perf/encodingAllocations.hs
- libraries/directory
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/jsbits/errno.js
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/haskeline
- libraries/process
- libraries/unix
- llvm-targets
- m4/fp_cc_supports_target.m4
- m4/fptools_set_platform_vars.m4
- m4/ghc_tables_next_to_code.m4
- rts/StgCRun.c
- rts/linker/PEi386.c
- rts/win32/veh_excn.c
- testsuite/tests/deSugar/should_compile/T10662.stderr
- testsuite/tests/deSugar/should_compile/T3263-1.stderr
- testsuite/tests/deSugar/should_compile/T3263-2.stderr
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
- utils/ghc-toolchain/exe/Main.hs
- utils/hsc2hs
- utils/llvm-targets/gen-data-layout.sh
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/285a4db0f397efbfbd8b4f4568cc3d…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/285a4db0f397efbfbd8b4f4568cc3d…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/spj-apporv-Oct24] look through PopErrCtxt while splitting exprs in application chains
by Apoorv Ingle (@ani) 06 May '25
by Apoorv Ingle (@ani) 06 May '25
06 May '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
285a4db0 by Apoorv Ingle at 2025-05-05T20:22:28-05:00
look through PopErrCtxt while splitting exprs in application chains
- - - - -
2 changed files:
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Head.hs
Changes:
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -413,11 +413,13 @@ tcApp rn_expr exp_res_ty
-- Step 2: Infer the type of `fun`, the head of the application
; (tc_fun, fun_sigma) <- tcInferAppHead fun
; let tc_head = (tc_fun, fun_ctxt)
- ; traceTc "tcApp:inferAppHead" $
- vcat [ text "tc_fun:" <+> ppr tc_fun
- , text "fun_sigma:" <+> ppr fun_sigma]
-- Step 3: Instantiate the function type (taking a quick look at args)
; do_ql <- wantQuickLook rn_fun
+ ; traceTc "tcApp:inferAppHead" $
+ vcat [ text "tc_fun:" <+> ppr tc_fun
+ , text "fun_sigma:" <+> ppr fun_sigma
+ , text "do_ql:" <+> ppr do_ql]
+
; (inst_args, app_res_rho)
<- tcInstFun do_ql True (tc_fun, rn_fun, fun_ctxt) fun_sigma rn_args
=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -300,6 +300,7 @@ splitHsApps e = go e (top_ctxt 0 e) []
top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun
top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun
top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun
+ top_ctxt n (XExpr (PopErrCtxt fun)) = top_ctxt n fun
top_ctxt n other_fun = VACall other_fun n noSrcSpan
top_lctxt :: Int -> LHsExpr GhcRn -> AppCtxt
@@ -332,6 +333,9 @@ splitHsApps e = go e (top_ctxt 0 e) []
-- and its hard to say exactly what that is
: EWrap (EExpand e)
: args )
+ go (XExpr (PopErrCtxt fun)) ctxt args = go fun ctxt args
+ -- look through PopErrCtxt (cf. T17594f) we do not want to lose the opportunity of calling tcEValArgQL
+ -- unlike HsPar, it is okay to forget about the PopErrCtxts as it does not persist over in GhcTc land
go e ctxt args = pure ((e,ctxt), args)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/285a4db0f397efbfbd8b4f4568cc3d1…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/285a4db0f397efbfbd8b4f4568cc3d1…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/spj-apporv-Oct24] accept test cases with changed error messages
by Apoorv Ingle (@ani) 05 May '25
by Apoorv Ingle (@ani) 05 May '25
05 May '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
92f2cb53 by Apoorv Ingle at 2025-05-05T18:58:47-05:00
accept test cases with changed error messages
-------------------------
Metric Decrease:
T9020
-------------------------
- - - - -
22 changed files:
- testsuite/tests/deSugar/should_compile/T10662.stderr
- testsuite/tests/deSugar/should_compile/T3263-1.stderr
- testsuite/tests/deSugar/should_compile/T3263-2.stderr
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
Changes:
=====================================
testsuite/tests/deSugar/should_compile/T10662.stderr
=====================================
@@ -1,6 +1,6 @@
-
-T10662.hs:3:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T10662.hs:2:8: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type ‘String’
Suggested fix:
Suppress this warning by saying
‘_ <- return $ let a = "hello" in a’
+
=====================================
testsuite/tests/deSugar/should_compile/T3263-1.stderr
=====================================
@@ -1,8 +1,8 @@
-
-T3263-1.hs:25:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T3263-1.hs:24:6: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type ‘Int’
Suggested fix: Suppress this warning by saying ‘_ <- nonNullM’
-T3263-1.hs:35:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T3263-1.hs:34:6: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type ‘Int’
Suggested fix: Suppress this warning by saying ‘_ <- nonNullM’
+
=====================================
testsuite/tests/deSugar/should_compile/T3263-2.stderr
=====================================
@@ -1,10 +1,10 @@
-
-T3263-2.hs:25:3: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
+T3263-2.hs:24:6: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
A do-notation statement discarded a result of type ‘m Int’
Suggested fix:
Suppress this warning by saying ‘_ <- return (return 10 :: m Int)’
-T3263-2.hs:37:3: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
+T3263-2.hs:36:6: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
A do-notation statement discarded a result of type ‘m Int’
Suggested fix:
Suppress this warning by saying ‘_ <- return (return 10 :: m Int)’
+
=====================================
testsuite/tests/default/default-fail05.stderr
=====================================
@@ -11,7 +11,7 @@ default-fail05.hs:11:10: error: [GHC-39999]
(use -fprint-potential-instances to see them all)
• In the first argument of ‘($)’, namely ‘toList’
In the first argument of ‘print’, namely ‘(toList $ pure 21)’
- In a stmt of a 'do' block: print (toList $ pure 21)
+ In the expression: print (toList $ pure 21)
default-fail05.hs:11:19: error: [GHC-39999]
• Ambiguous type variable ‘t0’ arising from a use of ‘pure’
@@ -25,7 +25,7 @@ default-fail05.hs:11:19: error: [GHC-39999]
(use -fprint-potential-instances to see them all)
• In the second argument of ‘($)’, namely ‘pure 21’
In the first argument of ‘print’, namely ‘(toList $ pure 21)’
- In a stmt of a 'do' block: print (toList $ pure 21)
+ In the expression: print (toList $ pure 21)
default-fail05.hs:12:3: error: [GHC-39999]
• Ambiguous type variable ‘t1’ arising from a use of ‘traverse’
=====================================
testsuite/tests/indexed-types/should_fail/T2693.stderr
=====================================
@@ -1,8 +1,7 @@
-
T2693.hs:12:15: error: [GHC-83865]
• Couldn't match expected type: (a8, b1)
with actual type: TFn a6
- The type variable ‘a6’ is ambiguous
+ The type variable ‘a6’ is ambiguous
• In the first argument of ‘fst’, namely ‘x’
In the first argument of ‘(+)’, namely ‘fst x’
In the expression: fst x + fst x
@@ -11,7 +10,7 @@ T2693.hs:12:15: error: [GHC-83865]
T2693.hs:12:23: error: [GHC-83865]
• Couldn't match expected type: (a8, b2)
with actual type: TFn a7
- The type variable ‘a7’ is ambiguous
+ The type variable ‘a7’ is ambiguous
• In the first argument of ‘fst’, namely ‘x’
In the second argument of ‘(+)’, namely ‘fst x’
In the expression: fst x + fst x
@@ -20,7 +19,7 @@ T2693.hs:12:23: error: [GHC-83865]
T2693.hs:19:15: error: [GHC-83865]
• Couldn't match expected type: (a5, b0)
with actual type: TFn a2
- The type variable ‘a2’ is ambiguous
+ The type variable ‘a2’ is ambiguous
• In the first argument of ‘fst’, namely ‘x’
In the first argument of ‘(+)’, namely ‘fst x’
In the expression: fst x + snd x
@@ -29,7 +28,7 @@ T2693.hs:19:15: error: [GHC-83865]
T2693.hs:19:23: error: [GHC-83865]
• Couldn't match expected type: (a4, a5)
with actual type: TFn a3
- The type variable ‘a3’ is ambiguous
+ The type variable ‘a3’ is ambiguous
• In the first argument of ‘snd’, namely ‘x’
In the second argument of ‘(+)’, namely ‘snd x’
In the expression: fst x + snd x
@@ -40,10 +39,11 @@ T2693.hs:29:20: error: [GHC-83865]
with: PVR a1
Expected: () -> Maybe (PVR a1)
Actual: () -> Maybe (TFn a0)
- The type variable ‘a0’ is ambiguous
+ The type variable ‘a0’ is ambiguous
• In the first argument of ‘mapM’, namely ‘g’
- In a stmt of a 'do' block: pvs <- mapM g undefined
+ In the expression: mapM g undefined
In the expression:
do pvs <- mapM g undefined
let n = (map pvrX pvs) `min` (map pvrX pvs)
undefined
+
=====================================
testsuite/tests/plugins/test-defaulting-plugin.stderr
=====================================
@@ -1,10 +1,9 @@
-
test-defaulting-plugin.hs:28:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
• Defaulting the type variable ‘a0’ to type ‘0’ in the following constraint
KnownNat a0 arising from a use of ‘q’
• In the first argument of ‘(+)’, namely ‘q’
In the second argument of ‘($)’, namely ‘q + w’
- In a stmt of a 'do' block: print $ q + w
+ In the expression: print $ q + w
test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
• Defaulting the type variable ‘a0’ to type ‘2’ in the following constraints
@@ -16,7 +15,7 @@ test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall
arising from a use of ‘w’ at test-defaulting-plugin.hs:28:15
• In the second argument of ‘(+)’, namely ‘w’
In the second argument of ‘($)’, namely ‘q + w’
- In a stmt of a 'do' block: print $ q + w
+ In the expression: print $ q + w
test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
• Defaulting the type variable ‘b0’ to type ‘0’ in the following constraint
@@ -35,3 +34,4 @@ test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall
In the expression:
do print $ q + w
print $ mc Proxy Proxy
+
=====================================
testsuite/tests/polykinds/T13393.stderr
=====================================
@@ -1,4 +1,3 @@
-
T13393.hs:61:3: error: [GHC-39999]
• Ambiguous type variable ‘t0’ arising from a use of ‘mapM’
prevents the constraint ‘(Traversable t0)’ from being solved.
@@ -11,7 +10,7 @@ T13393.hs:61:3: error: [GHC-39999]
...plus four others
...plus 27 instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
- • In a stmt of a 'do' block:
+ • In the expression:
mapM putBackLeftOverInputAndReturnOutput undefined
In the expression:
do mapM putBackLeftOverInputAndReturnOutput undefined
@@ -24,3 +23,4 @@ T13393.hs:61:3: error: [GHC-39999]
putBackLeftOverInputAndReturnOutput (MkEncodeResult x)
= do leftOvers .= x
....
+
=====================================
testsuite/tests/printer/T17697.stderr
=====================================
@@ -1,8 +1,8 @@
-T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)]
- Variable not in scope: threadDelay :: t0 -> IO a0
-
-T17697.hs:6:5: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T17697.hs:5:8: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type
‘GHC.Internal.Types.ZonkAny 1’
Suggested fix: Suppress this warning by saying ‘_ <- threadDelay 1’
+T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)]
+ Variable not in scope: threadDelay :: t0 -> IO a0
+
=====================================
testsuite/tests/typecheck/should_compile/T14590.stderr
=====================================
@@ -1,7 +1,6 @@
-T14590.hs:4:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
• Found hole: _ :: Int -> Int -> Int
- • In the expression: x `_`
- In the expression: (x `_`) y
+ • In the expression: (x `_`) y
In an equation for ‘f1’: f1 x y = (x `_`) y
• Relevant bindings include
y :: Int (bound at T14590.hs:4:6)
@@ -85,11 +84,10 @@ T14590.hs:4:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
(imported from ‘Prelude’ at T14590.hs:1:8-13
(and originally defined in ‘GHC.Internal.Base’))
-T14590.hs:5:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
• Found hole: _a :: Int -> Int -> Int
Or perhaps ‘_a’ is mis-spelled, or not in scope
- • In the expression: x `_a`
- In the expression: (x `_a`) y
+ • In the expression: (x `_a`) y
In an equation for ‘f2’: f2 x y = (x `_a`) y
• Relevant bindings include
y :: Int (bound at T14590.hs:5:6)
=====================================
testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
=====================================
@@ -11,7 +11,7 @@ valid_hole_fits.hs:9:6: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables
valid_hole_fits.hs:17:17: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
• Found hole: _ :: Int -> IO Int
- • In a stmt of a 'do' block: y <- _ x
+ • In the expression: _ x
In the expression:
do x <- a 0
y <- _ x
=====================================
testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
=====================================
@@ -1,4 +1,3 @@
-
DoExpansion1.hs:7:19: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
• No instance for ‘Num String’ arising from the literal ‘1’
• In the first argument of ‘putStrLn’, namely ‘1’
@@ -23,7 +22,7 @@ DoExpansion1.hs:15:54: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul
DoExpansion1.hs:19:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
• No instance for ‘Num String’ arising from the literal ‘1’
• In the first argument of ‘putStrLn’, namely ‘1’
- In a stmt of a 'do' block: putStrLn 1
+ In the expression: putStrLn 1
In the expression:
do putStrLn 1
putStrLn "r2"
@@ -32,7 +31,7 @@ DoExpansion1.hs:19:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul
DoExpansion1.hs:25:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
• No instance for ‘Num String’ arising from the literal ‘2’
• In the first argument of ‘putStrLn’, namely ‘2’
- In a stmt of a 'do' block: putStrLn 2
+ In the expression: putStrLn 2
In the expression:
do putStrLn "r1"
putStrLn 2
@@ -46,3 +45,4 @@ DoExpansion1.hs:32:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul
do putStrLn "r1"
putStrLn "r2"
putStrLn 3
+
=====================================
testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
=====================================
@@ -1,4 +1,3 @@
-
DoExpansion2.hs:13:20: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
• Couldn't match expected type ‘Int’ with actual type ‘Char’
• In the first argument of ‘(+)’, namely ‘x’
@@ -57,7 +56,7 @@ DoExpansion2.hs:34:22: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul
with actual type: IO String
• The function ‘getVal’ is applied to two visible arguments,
but its type ‘Int -> IO String’ has only one
- In a stmt of a 'do' block: Just x <- getVal 3 4
+ In the expression: getVal 3 4
In the expression:
do Just x <- getVal 3 4
return x
@@ -71,3 +70,4 @@ DoExpansion2.hs:39:19: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul
In the expression:
do x <- getVal 3
return x
+
=====================================
testsuite/tests/typecheck/should_fail/T10971d.stderr
=====================================
@@ -1,17 +1,16 @@
-
T10971d.hs:4:14: error: [GHC-83865]
• Couldn't match expected type: [a0]
with actual type: Maybe a3
• In the first argument of ‘f’, namely ‘(Just 1)’
In the second argument of ‘($)’, namely ‘f (Just 1)’
- In a stmt of a 'do' block: print $ f (Just 1)
+ In the expression: print $ f (Just 1)
T10971d.hs:5:19: error: [GHC-83865]
• Couldn't match expected type: [b0]
with actual type: Maybe a4
• In the second argument of ‘g’, namely ‘(Just 5)’
In the second argument of ‘($)’, namely ‘g (+ 1) (Just 5)’
- In a stmt of a 'do' block: print $ g (+ 1) (Just 5)
+ In the expression: print $ g (+ 1) (Just 5)
T10971d.hs:6:23: error: [GHC-83865]
• Couldn't match expected type: [a2]
@@ -19,3 +18,4 @@ T10971d.hs:6:23: error: [GHC-83865]
• In the second argument of ‘h’, namely ‘Nothing’
In the second argument of ‘($)’, namely ‘h (const 5) Nothing’
In a stmt of a 'do' block: print $ h (const 5) Nothing
+
=====================================
testsuite/tests/typecheck/should_fail/T13311.stderr
=====================================
@@ -1,12 +1,12 @@
-
T13311.hs:9:3: error: [GHC-83865]
• Couldn't match expected type: IO a0
with actual type: Maybe a1 -> Maybe b0
• Probable cause: ‘f’ is applied to too few arguments
- In a stmt of a 'do' block: f
+ In the expression: f
In the expression:
do f
putChar 'a'
In an equation for ‘g’:
g = do f
putChar 'a'
+
=====================================
testsuite/tests/typecheck/should_fail/T24064.stderr
=====================================
@@ -1,4 +1,3 @@
-
T24064.hs:42:3: error: [GHC-25897]
• Could not deduce ‘m ~ X e0’
from the context: (C2 m, F2 m ~ Y)
@@ -11,7 +10,7 @@ T24064.hs:42:3: error: [GHC-25897]
the type signature for:
test :: forall (m :: * -> *). (C2 m, F2 m ~ Y) => m ()
at T24064.hs:40:1-32
- • In a stmt of a 'do' block: fun1
+ • In the expression: fun1
In the expression:
do fun1
fun2
@@ -24,3 +23,4 @@ T24064.hs:42:3: error: [GHC-25897]
g fun3
....
• Relevant bindings include test :: m () (bound at T24064.hs:41:1)
+
=====================================
testsuite/tests/typecheck/should_fail/T3613.stderr
=====================================
@@ -1,4 +1,3 @@
-
T3613.hs:14:20: error: [GHC-83865]
• Couldn't match type ‘IO’ with ‘Maybe’
Expected: Maybe ()
@@ -11,7 +10,7 @@ T3613.hs:17:24: error: [GHC-83865]
• Couldn't match type ‘IO’ with ‘Maybe’
Expected: Maybe ()
Actual: IO ()
- • In a stmt of a 'do' block: bar
+ • In the expression: bar
In the first argument of ‘fooThen’, namely
‘(do bar
undefined)’
@@ -19,3 +18,4 @@ T3613.hs:17:24: error: [GHC-83865]
fooThen
(do bar
undefined)
+
=====================================
testsuite/tests/typecheck/should_fail/T7851.stderr
=====================================
@@ -1,9 +1,8 @@
-
T7851.hs:5:10: error: [GHC-83865]
• Couldn't match expected type: IO a0
with actual type: a1 -> IO ()
• Probable cause: ‘print’ is applied to too few arguments
- In a stmt of a 'do' block: print
+ In the expression: print
In the expression:
do print
print "Hello"
@@ -11,3 +10,4 @@ T7851.hs:5:10: error: [GHC-83865]
bar
= do print
print "Hello"
+
=====================================
testsuite/tests/typecheck/should_fail/T8603.stderr
=====================================
@@ -1,4 +1,3 @@
-
T8603.hs:33:17: error: [GHC-18872]
• Couldn't match kind ‘* -> *’ with ‘*’
When matching types
@@ -10,7 +9,7 @@ T8603.hs:33:17: error: [GHC-18872]
but its type ‘(Control.Monad.Trans.Class.MonadTrans t, Monad m) =>
m a -> t m a’
has only one
- In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3]
+ In the expression: lift uniform [1, 2, 3]
In the expression:
do prize <- lift uniform [1, 2, ....]
return False
@@ -21,9 +20,10 @@ T8603.hs:33:22: error: [GHC-83865]
Expected: [a1] -> StateT s RV a0
Actual: [a1] -> RV a1
• In the first argument of ‘lift’, namely ‘uniform’
- In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3]
+ In the expression: lift uniform [1, 2, 3]
In the expression:
do prize <- lift uniform [1, 2, ....]
return False
• Relevant bindings include
testRVState1 :: RVState s Bool (bound at T8603.hs:32:1)
+
=====================================
testsuite/tests/typecheck/should_fail/T9612.stderr
=====================================
@@ -1,4 +1,3 @@
-
T9612.hs:16:9: error: [GHC-18872]
• Couldn't match type: [(Int, a)]
with: (Int, a)
@@ -6,7 +5,7 @@ T9612.hs:16:9: error: [GHC-18872]
constraint ‘MonadWriter (Int, a) (WriterT [(Int, a)] Identity)’
arising from a use of ‘tell’
instance ‘MonadWriter w (WriterT w m)’ at T9612.hs:20:10-59
- • In a stmt of a 'do' block: tell (n, x)
+ • In the expression: tell (n, x)
In the expression:
do tell (n, x)
return (1, y)
@@ -19,3 +18,4 @@ T9612.hs:16:9: error: [GHC-18872]
y :: a (bound at T9612.hs:14:3)
f :: a -> (Int, a) -> Writer [(Int, a)] (Int, a)
(bound at T9612.hs:14:1)
+
=====================================
testsuite/tests/typecheck/should_fail/tcfail128.stderr
=====================================
@@ -1,4 +1,3 @@
-
tcfail128.hs:18:16: error: [GHC-39999]
• Ambiguous type variable ‘b0’ arising from a use of ‘thaw’
prevents the constraint ‘(Data.Array.Base.MArray
@@ -6,7 +5,7 @@ tcfail128.hs:18:16: error: [GHC-39999]
Probable fix: use a type annotation to specify what ‘b0’ should be.
one instance involving out-of-scope types
(use -fprint-potential-instances to see them all)
- • In a stmt of a 'do' block: v <- thaw tmp
+ • In the expression: thaw tmp
In the expression:
do let sL = ...
dim = length sL
@@ -19,3 +18,4 @@ tcfail128.hs:18:16: error: [GHC-39999]
....
v <- thaw tmp
return ()
+
=====================================
testsuite/tests/typecheck/should_fail/tcfail168.stderr
=====================================
@@ -1,9 +1,8 @@
-
tcfail168.hs:7:11: error: [GHC-83865]
• Couldn't match expected type: IO a0
with actual type: Char -> IO ()
• Probable cause: ‘putChar’ is applied to too few arguments
- In a stmt of a 'do' block: putChar
+ In the expression: putChar
In the expression:
do putChar
putChar 'a'
@@ -16,3 +15,4 @@ tcfail168.hs:7:11: error: [GHC-83865]
putChar 'a'
putChar 'a'
....
+
=====================================
testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
=====================================
@@ -1,7 +1,7 @@
CaretDiagnostics1.hs:7:8-15: error: [GHC-83865]
• Couldn't match expected type ‘IO a0’ with actual type ‘Int’
• In the second argument of ‘(+)’, namely ‘(3 :: Int)’
- In a stmt of a 'do' block:
+ In the expression:
10000000000000000000000000000000000000 + 2 + (3 :: Int)
In the expression:
do 10000000000000000000000000000000000000 + 2 + (3 :: Int)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92f2cb533a672e6288ab7e5ab5a03fa…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/92f2cb533a672e6288ab7e5ab5a03fa…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/spj-apporv-Oct24] accept test cases with changed error messages
by Apoorv Ingle (@ani) 05 May '25
by Apoorv Ingle (@ani) 05 May '25
05 May '25
Apoorv Ingle pushed to branch wip/spj-apporv-Oct24 at Glasgow Haskell Compiler / GHC
Commits:
28caa69a by Apoorv Ingle at 2025-05-05T18:53:34-05:00
accept test cases with changed error messages
- - - - -
22 changed files:
- testsuite/tests/deSugar/should_compile/T10662.stderr
- testsuite/tests/deSugar/should_compile/T3263-1.stderr
- testsuite/tests/deSugar/should_compile/T3263-2.stderr
- testsuite/tests/default/default-fail05.stderr
- testsuite/tests/indexed-types/should_fail/T2693.stderr
- testsuite/tests/plugins/test-defaulting-plugin.stderr
- testsuite/tests/polykinds/T13393.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/typecheck/should_compile/T14590.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
- testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
- testsuite/tests/typecheck/should_fail/T10971d.stderr
- testsuite/tests/typecheck/should_fail/T13311.stderr
- testsuite/tests/typecheck/should_fail/T24064.stderr
- testsuite/tests/typecheck/should_fail/T3613.stderr
- testsuite/tests/typecheck/should_fail/T7851.stderr
- testsuite/tests/typecheck/should_fail/T8603.stderr
- testsuite/tests/typecheck/should_fail/T9612.stderr
- testsuite/tests/typecheck/should_fail/tcfail128.stderr
- testsuite/tests/typecheck/should_fail/tcfail168.stderr
- testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
Changes:
=====================================
testsuite/tests/deSugar/should_compile/T10662.stderr
=====================================
@@ -1,6 +1,6 @@
-
-T10662.hs:3:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T10662.hs:2:8: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type ‘String’
Suggested fix:
Suppress this warning by saying
‘_ <- return $ let a = "hello" in a’
+
=====================================
testsuite/tests/deSugar/should_compile/T3263-1.stderr
=====================================
@@ -1,8 +1,8 @@
-
-T3263-1.hs:25:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T3263-1.hs:24:6: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type ‘Int’
Suggested fix: Suppress this warning by saying ‘_ <- nonNullM’
-T3263-1.hs:35:3: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T3263-1.hs:34:6: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type ‘Int’
Suggested fix: Suppress this warning by saying ‘_ <- nonNullM’
+
=====================================
testsuite/tests/deSugar/should_compile/T3263-2.stderr
=====================================
@@ -1,10 +1,10 @@
-
-T3263-2.hs:25:3: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
+T3263-2.hs:24:6: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
A do-notation statement discarded a result of type ‘m Int’
Suggested fix:
Suppress this warning by saying ‘_ <- return (return 10 :: m Int)’
-T3263-2.hs:37:3: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
+T3263-2.hs:36:6: warning: [GHC-08838] [-Wwrong-do-bind (in -Wdefault)]
A do-notation statement discarded a result of type ‘m Int’
Suggested fix:
Suppress this warning by saying ‘_ <- return (return 10 :: m Int)’
+
=====================================
testsuite/tests/default/default-fail05.stderr
=====================================
@@ -11,7 +11,7 @@ default-fail05.hs:11:10: error: [GHC-39999]
(use -fprint-potential-instances to see them all)
• In the first argument of ‘($)’, namely ‘toList’
In the first argument of ‘print’, namely ‘(toList $ pure 21)’
- In a stmt of a 'do' block: print (toList $ pure 21)
+ In the expression: print (toList $ pure 21)
default-fail05.hs:11:19: error: [GHC-39999]
• Ambiguous type variable ‘t0’ arising from a use of ‘pure’
@@ -25,7 +25,7 @@ default-fail05.hs:11:19: error: [GHC-39999]
(use -fprint-potential-instances to see them all)
• In the second argument of ‘($)’, namely ‘pure 21’
In the first argument of ‘print’, namely ‘(toList $ pure 21)’
- In a stmt of a 'do' block: print (toList $ pure 21)
+ In the expression: print (toList $ pure 21)
default-fail05.hs:12:3: error: [GHC-39999]
• Ambiguous type variable ‘t1’ arising from a use of ‘traverse’
=====================================
testsuite/tests/indexed-types/should_fail/T2693.stderr
=====================================
@@ -1,8 +1,7 @@
-
T2693.hs:12:15: error: [GHC-83865]
• Couldn't match expected type: (a8, b1)
with actual type: TFn a6
- The type variable ‘a6’ is ambiguous
+ The type variable ‘a6’ is ambiguous
• In the first argument of ‘fst’, namely ‘x’
In the first argument of ‘(+)’, namely ‘fst x’
In the expression: fst x + fst x
@@ -11,7 +10,7 @@ T2693.hs:12:15: error: [GHC-83865]
T2693.hs:12:23: error: [GHC-83865]
• Couldn't match expected type: (a8, b2)
with actual type: TFn a7
- The type variable ‘a7’ is ambiguous
+ The type variable ‘a7’ is ambiguous
• In the first argument of ‘fst’, namely ‘x’
In the second argument of ‘(+)’, namely ‘fst x’
In the expression: fst x + fst x
@@ -20,7 +19,7 @@ T2693.hs:12:23: error: [GHC-83865]
T2693.hs:19:15: error: [GHC-83865]
• Couldn't match expected type: (a5, b0)
with actual type: TFn a2
- The type variable ‘a2’ is ambiguous
+ The type variable ‘a2’ is ambiguous
• In the first argument of ‘fst’, namely ‘x’
In the first argument of ‘(+)’, namely ‘fst x’
In the expression: fst x + snd x
@@ -29,7 +28,7 @@ T2693.hs:19:15: error: [GHC-83865]
T2693.hs:19:23: error: [GHC-83865]
• Couldn't match expected type: (a4, a5)
with actual type: TFn a3
- The type variable ‘a3’ is ambiguous
+ The type variable ‘a3’ is ambiguous
• In the first argument of ‘snd’, namely ‘x’
In the second argument of ‘(+)’, namely ‘snd x’
In the expression: fst x + snd x
@@ -40,10 +39,11 @@ T2693.hs:29:20: error: [GHC-83865]
with: PVR a1
Expected: () -> Maybe (PVR a1)
Actual: () -> Maybe (TFn a0)
- The type variable ‘a0’ is ambiguous
+ The type variable ‘a0’ is ambiguous
• In the first argument of ‘mapM’, namely ‘g’
- In a stmt of a 'do' block: pvs <- mapM g undefined
+ In the expression: mapM g undefined
In the expression:
do pvs <- mapM g undefined
let n = (map pvrX pvs) `min` (map pvrX pvs)
undefined
+
=====================================
testsuite/tests/plugins/test-defaulting-plugin.stderr
=====================================
@@ -1,10 +1,9 @@
-
test-defaulting-plugin.hs:28:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
• Defaulting the type variable ‘a0’ to type ‘0’ in the following constraint
KnownNat a0 arising from a use of ‘q’
• In the first argument of ‘(+)’, namely ‘q’
In the second argument of ‘($)’, namely ‘q + w’
- In a stmt of a 'do' block: print $ q + w
+ In the expression: print $ q + w
test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
• Defaulting the type variable ‘a0’ to type ‘2’ in the following constraints
@@ -16,7 +15,7 @@ test-defaulting-plugin.hs:28:15: warning: [GHC-18042] [-Wtype-defaults (in -Wall
arising from a use of ‘w’ at test-defaulting-plugin.hs:28:15
• In the second argument of ‘(+)’, namely ‘w’
In the second argument of ‘($)’, namely ‘q + w’
- In a stmt of a 'do' block: print $ q + w
+ In the expression: print $ q + w
test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall)]
• Defaulting the type variable ‘b0’ to type ‘0’ in the following constraint
@@ -35,3 +34,4 @@ test-defaulting-plugin.hs:29:11: warning: [GHC-18042] [-Wtype-defaults (in -Wall
In the expression:
do print $ q + w
print $ mc Proxy Proxy
+
=====================================
testsuite/tests/polykinds/T13393.stderr
=====================================
@@ -1,4 +1,3 @@
-
T13393.hs:61:3: error: [GHC-39999]
• Ambiguous type variable ‘t0’ arising from a use of ‘mapM’
prevents the constraint ‘(Traversable t0)’ from being solved.
@@ -11,7 +10,7 @@ T13393.hs:61:3: error: [GHC-39999]
...plus four others
...plus 27 instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
- • In a stmt of a 'do' block:
+ • In the expression:
mapM putBackLeftOverInputAndReturnOutput undefined
In the expression:
do mapM putBackLeftOverInputAndReturnOutput undefined
@@ -24,3 +23,4 @@ T13393.hs:61:3: error: [GHC-39999]
putBackLeftOverInputAndReturnOutput (MkEncodeResult x)
= do leftOvers .= x
....
+
=====================================
testsuite/tests/printer/T17697.stderr
=====================================
@@ -1,8 +1,8 @@
-T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)]
- Variable not in scope: threadDelay :: t0 -> IO a0
-
-T17697.hs:6:5: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
+T17697.hs:5:8: warning: [GHC-81995] [-Wunused-do-bind (in -Wall)]
A do-notation statement discarded a result of type
‘GHC.Internal.Types.ZonkAny 1’
Suggested fix: Suppress this warning by saying ‘_ <- threadDelay 1’
+T17697.hs:6:5: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables (in -Wdefault)]
+ Variable not in scope: threadDelay :: t0 -> IO a0
+
=====================================
testsuite/tests/typecheck/should_compile/T14590.stderr
=====================================
@@ -1,7 +1,6 @@
-T14590.hs:4:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+T14590.hs:4:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
• Found hole: _ :: Int -> Int -> Int
- • In the expression: x `_`
- In the expression: (x `_`) y
+ • In the expression: (x `_`) y
In an equation for ‘f1’: f1 x y = (x `_`) y
• Relevant bindings include
y :: Int (bound at T14590.hs:4:6)
@@ -85,11 +84,10 @@ T14590.hs:4:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
(imported from ‘Prelude’ at T14590.hs:1:8-13
(and originally defined in ‘GHC.Internal.Base’))
-T14590.hs:5:11: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
+T14590.hs:5:13: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
• Found hole: _a :: Int -> Int -> Int
Or perhaps ‘_a’ is mis-spelled, or not in scope
- • In the expression: x `_a`
- In the expression: (x `_a`) y
+ • In the expression: (x `_a`) y
In an equation for ‘f2’: f2 x y = (x `_a`) y
• Relevant bindings include
y :: Int (bound at T14590.hs:5:6)
=====================================
testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
=====================================
@@ -11,7 +11,7 @@ valid_hole_fits.hs:9:6: warning: [GHC-88464] [-Wdeferred-out-of-scope-variables
valid_hole_fits.hs:17:17: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
• Found hole: _ :: Int -> IO Int
- • In a stmt of a 'do' block: y <- _ x
+ • In the expression: _ x
In the expression:
do x <- a 0
y <- _ x
=====================================
testsuite/tests/typecheck/should_fail/DoExpansion1.stderr
=====================================
@@ -1,4 +1,3 @@
-
DoExpansion1.hs:7:19: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
• No instance for ‘Num String’ arising from the literal ‘1’
• In the first argument of ‘putStrLn’, namely ‘1’
@@ -23,7 +22,7 @@ DoExpansion1.hs:15:54: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul
DoExpansion1.hs:19:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
• No instance for ‘Num String’ arising from the literal ‘1’
• In the first argument of ‘putStrLn’, namely ‘1’
- In a stmt of a 'do' block: putStrLn 1
+ In the expression: putStrLn 1
In the expression:
do putStrLn 1
putStrLn "r2"
@@ -32,7 +31,7 @@ DoExpansion1.hs:19:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul
DoExpansion1.hs:25:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefault)]
• No instance for ‘Num String’ arising from the literal ‘2’
• In the first argument of ‘putStrLn’, namely ‘2’
- In a stmt of a 'do' block: putStrLn 2
+ In the expression: putStrLn 2
In the expression:
do putStrLn "r1"
putStrLn 2
@@ -46,3 +45,4 @@ DoExpansion1.hs:32:21: warning: [GHC-39999] [-Wdeferred-type-errors (in -Wdefaul
do putStrLn "r1"
putStrLn "r2"
putStrLn 3
+
=====================================
testsuite/tests/typecheck/should_fail/DoExpansion2.stderr
=====================================
@@ -1,4 +1,3 @@
-
DoExpansion2.hs:13:20: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)]
• Couldn't match expected type ‘Int’ with actual type ‘Char’
• In the first argument of ‘(+)’, namely ‘x’
@@ -57,7 +56,7 @@ DoExpansion2.hs:34:22: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul
with actual type: IO String
• The function ‘getVal’ is applied to two visible arguments,
but its type ‘Int -> IO String’ has only one
- In a stmt of a 'do' block: Just x <- getVal 3 4
+ In the expression: getVal 3 4
In the expression:
do Just x <- getVal 3 4
return x
@@ -71,3 +70,4 @@ DoExpansion2.hs:39:19: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefaul
In the expression:
do x <- getVal 3
return x
+
=====================================
testsuite/tests/typecheck/should_fail/T10971d.stderr
=====================================
@@ -1,17 +1,16 @@
-
T10971d.hs:4:14: error: [GHC-83865]
• Couldn't match expected type: [a0]
with actual type: Maybe a3
• In the first argument of ‘f’, namely ‘(Just 1)’
In the second argument of ‘($)’, namely ‘f (Just 1)’
- In a stmt of a 'do' block: print $ f (Just 1)
+ In the expression: print $ f (Just 1)
T10971d.hs:5:19: error: [GHC-83865]
• Couldn't match expected type: [b0]
with actual type: Maybe a4
• In the second argument of ‘g’, namely ‘(Just 5)’
In the second argument of ‘($)’, namely ‘g (+ 1) (Just 5)’
- In a stmt of a 'do' block: print $ g (+ 1) (Just 5)
+ In the expression: print $ g (+ 1) (Just 5)
T10971d.hs:6:23: error: [GHC-83865]
• Couldn't match expected type: [a2]
@@ -19,3 +18,4 @@ T10971d.hs:6:23: error: [GHC-83865]
• In the second argument of ‘h’, namely ‘Nothing’
In the second argument of ‘($)’, namely ‘h (const 5) Nothing’
In a stmt of a 'do' block: print $ h (const 5) Nothing
+
=====================================
testsuite/tests/typecheck/should_fail/T13311.stderr
=====================================
@@ -1,12 +1,12 @@
-
T13311.hs:9:3: error: [GHC-83865]
• Couldn't match expected type: IO a0
with actual type: Maybe a1 -> Maybe b0
• Probable cause: ‘f’ is applied to too few arguments
- In a stmt of a 'do' block: f
+ In the expression: f
In the expression:
do f
putChar 'a'
In an equation for ‘g’:
g = do f
putChar 'a'
+
=====================================
testsuite/tests/typecheck/should_fail/T24064.stderr
=====================================
@@ -1,4 +1,3 @@
-
T24064.hs:42:3: error: [GHC-25897]
• Could not deduce ‘m ~ X e0’
from the context: (C2 m, F2 m ~ Y)
@@ -11,7 +10,7 @@ T24064.hs:42:3: error: [GHC-25897]
the type signature for:
test :: forall (m :: * -> *). (C2 m, F2 m ~ Y) => m ()
at T24064.hs:40:1-32
- • In a stmt of a 'do' block: fun1
+ • In the expression: fun1
In the expression:
do fun1
fun2
@@ -24,3 +23,4 @@ T24064.hs:42:3: error: [GHC-25897]
g fun3
....
• Relevant bindings include test :: m () (bound at T24064.hs:41:1)
+
=====================================
testsuite/tests/typecheck/should_fail/T3613.stderr
=====================================
@@ -1,4 +1,3 @@
-
T3613.hs:14:20: error: [GHC-83865]
• Couldn't match type ‘IO’ with ‘Maybe’
Expected: Maybe ()
@@ -11,7 +10,7 @@ T3613.hs:17:24: error: [GHC-83865]
• Couldn't match type ‘IO’ with ‘Maybe’
Expected: Maybe ()
Actual: IO ()
- • In a stmt of a 'do' block: bar
+ • In the expression: bar
In the first argument of ‘fooThen’, namely
‘(do bar
undefined)’
@@ -19,3 +18,4 @@ T3613.hs:17:24: error: [GHC-83865]
fooThen
(do bar
undefined)
+
=====================================
testsuite/tests/typecheck/should_fail/T7851.stderr
=====================================
@@ -1,9 +1,8 @@
-
T7851.hs:5:10: error: [GHC-83865]
• Couldn't match expected type: IO a0
with actual type: a1 -> IO ()
• Probable cause: ‘print’ is applied to too few arguments
- In a stmt of a 'do' block: print
+ In the expression: print
In the expression:
do print
print "Hello"
@@ -11,3 +10,4 @@ T7851.hs:5:10: error: [GHC-83865]
bar
= do print
print "Hello"
+
=====================================
testsuite/tests/typecheck/should_fail/T8603.stderr
=====================================
@@ -1,4 +1,3 @@
-
T8603.hs:33:17: error: [GHC-18872]
• Couldn't match kind ‘* -> *’ with ‘*’
When matching types
@@ -10,7 +9,7 @@ T8603.hs:33:17: error: [GHC-18872]
but its type ‘(Control.Monad.Trans.Class.MonadTrans t, Monad m) =>
m a -> t m a’
has only one
- In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3]
+ In the expression: lift uniform [1, 2, 3]
In the expression:
do prize <- lift uniform [1, 2, ....]
return False
@@ -21,9 +20,10 @@ T8603.hs:33:22: error: [GHC-83865]
Expected: [a1] -> StateT s RV a0
Actual: [a1] -> RV a1
• In the first argument of ‘lift’, namely ‘uniform’
- In a stmt of a 'do' block: prize <- lift uniform [1, 2, 3]
+ In the expression: lift uniform [1, 2, 3]
In the expression:
do prize <- lift uniform [1, 2, ....]
return False
• Relevant bindings include
testRVState1 :: RVState s Bool (bound at T8603.hs:32:1)
+
=====================================
testsuite/tests/typecheck/should_fail/T9612.stderr
=====================================
@@ -1,4 +1,3 @@
-
T9612.hs:16:9: error: [GHC-18872]
• Couldn't match type: [(Int, a)]
with: (Int, a)
@@ -6,7 +5,7 @@ T9612.hs:16:9: error: [GHC-18872]
constraint ‘MonadWriter (Int, a) (WriterT [(Int, a)] Identity)’
arising from a use of ‘tell’
instance ‘MonadWriter w (WriterT w m)’ at T9612.hs:20:10-59
- • In a stmt of a 'do' block: tell (n, x)
+ • In the expression: tell (n, x)
In the expression:
do tell (n, x)
return (1, y)
@@ -19,3 +18,4 @@ T9612.hs:16:9: error: [GHC-18872]
y :: a (bound at T9612.hs:14:3)
f :: a -> (Int, a) -> Writer [(Int, a)] (Int, a)
(bound at T9612.hs:14:1)
+
=====================================
testsuite/tests/typecheck/should_fail/tcfail128.stderr
=====================================
@@ -1,4 +1,3 @@
-
tcfail128.hs:18:16: error: [GHC-39999]
• Ambiguous type variable ‘b0’ arising from a use of ‘thaw’
prevents the constraint ‘(Data.Array.Base.MArray
@@ -6,7 +5,7 @@ tcfail128.hs:18:16: error: [GHC-39999]
Probable fix: use a type annotation to specify what ‘b0’ should be.
one instance involving out-of-scope types
(use -fprint-potential-instances to see them all)
- • In a stmt of a 'do' block: v <- thaw tmp
+ • In the expression: thaw tmp
In the expression:
do let sL = ...
dim = length sL
@@ -19,3 +18,4 @@ tcfail128.hs:18:16: error: [GHC-39999]
....
v <- thaw tmp
return ()
+
=====================================
testsuite/tests/typecheck/should_fail/tcfail168.stderr
=====================================
@@ -1,9 +1,8 @@
-
tcfail168.hs:7:11: error: [GHC-83865]
• Couldn't match expected type: IO a0
with actual type: Char -> IO ()
• Probable cause: ‘putChar’ is applied to too few arguments
- In a stmt of a 'do' block: putChar
+ In the expression: putChar
In the expression:
do putChar
putChar 'a'
@@ -16,3 +15,4 @@ tcfail168.hs:7:11: error: [GHC-83865]
putChar 'a'
putChar 'a'
....
+
=====================================
testsuite/tests/warnings/should_fail/CaretDiagnostics1.stderr
=====================================
@@ -1,7 +1,7 @@
CaretDiagnostics1.hs:7:8-15: error: [GHC-83865]
• Couldn't match expected type ‘IO a0’ with actual type ‘Int’
• In the second argument of ‘(+)’, namely ‘(3 :: Int)’
- In a stmt of a 'do' block:
+ In the expression:
10000000000000000000000000000000000000 + 2 + (3 :: Int)
In the expression:
do 10000000000000000000000000000000000000 + 2 + (3 :: Int)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28caa69a244799f9a48b3826be1b787…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28caa69a244799f9a48b3826be1b787…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T26003] 9 commits: Fix lexing "\^\" (#25937)
by Simon Peyton Jones (@simonpj) 05 May '25
by Simon Peyton Jones (@simonpj) 05 May '25
05 May '25
Simon Peyton Jones pushed to branch wip/T26003 at Glasgow Haskell Compiler / GHC
Commits:
6467d61e by Brandon Chinn at 2025-04-29T18:36:03-04:00
Fix lexing "\^\" (#25937)
This broke in the refactor in !13128, where the old code parsed escape
codes and collapsed string gaps at the same time, but the new code
collapsed gaps first, then resolved escape codes. The new code used a
naive heuristic to skip escaped backslashes, but didn't account for
"\^\".
- - - - -
99868a86 by Jens Petersen at 2025-04-29T18:36:44-04:00
hadrian: default selftest to disabled
- - - - -
aba2a4a5 by Zubin Duggal at 2025-04-30T06:35:59-04:00
get-win32-tarballs.py: List tarball files to be downloaded if we cannot find them
Fixes #25929
- - - - -
d99a617b by Ben Gamari at 2025-04-30T06:36:40-04:00
Move Data ModuleName instance to Language.Haskell.Syntax.Module.Name
Fixes #25968.
- - - - -
9995c2b7 by Serge S. Gulin at 2025-05-04T17:13:36+03:00
Support for ARM64 Windows (LLVM-enabled) (fixes #24603)
1. Add Windows AArch64 cross-compilation support via CI jobs
Introduce new CI configurations for cross-compiling to Windows ARM64 using Debian12Wine, FEX, and MSYS2.
Configure toolchain variables for LLVM MinGW and Wine emulation in CI pipelines.
2. Adjust compiler and RTS for AArch64 Windows compatibility
Reserve register `x18` on Windows and Darwin platforms in AArch64 codegen.
Handle Windows-specific relocations and data sections in AArch64 assembler.
Update PEi386 linker to recognize ARM64 binaries and support exception handling.
Adjust LLVM target definitions and data layouts for new architectures.
Update `ghc-toolchain` and build scripts to handle `TablesNextToCode` on Windows ARM64.
3. Enhance CI scripts and stability
Modify `ci.sh` to handle mingw cross-targets, fixing GHC executable paths and test execution.
Use `diff -w` in tests to ignore whitespace differences, improving cross-platform consistency.
4. Refactor and clean up code
Remove redundant imports in hello.hs test.
Improve error messages and checks for unsupported configurations in the driver.
Add `EXDEV` error code to `errno.js`.
Add async/sync flags to IO logs at `base.js`.
Improve POSIX compatibility for file close at `base.js`: decrease indeterminism for mixed cases of async and sync code.
5. Update dependencies: `Cabal`, `Win32`, `directory`, `process`, `haskeline`, and `unix`.
submodule
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
Co-authored-by: Dmitrii Egorov <egorov.d.i(a)icloud.com>
Co-authored-by: Andrei Borzenkov <root(a)sandwitch.dev>
- - - - -
50fa8165 by Javran Cheng at 2025-05-05T05:55:39-04:00
Suppress unused do-binding if discarded variable is Any or ZonkAny.
Consider example (#25895):
> do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`.
Nothing constrains `b`, so it will be instantiates with `Any` or
`ZonkAny`.
But we certainly don't want to complain about a discarded do-binding.
Fixes #25895
- - - - -
1353f40d by Simon Peyton Jones at 2025-05-05T17:51:27+01:00
Wip on #26003
- - - - -
7b42c862 by Simon Peyton Jones at 2025-05-05T17:51:27+01:00
Wibbles
- - - - -
c763d3a8 by Simon Peyton Jones at 2025-05-05T19:16:57+01:00
Further wibbles
- - - - -
61 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/hello.hs
- .gitlab/jobs.yaml
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/String.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Unit/Types.hs
- compiler/Language/Haskell/Syntax/Module/Name.hs
- hadrian/README.md
- hadrian/hadrian.cabal
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/BinaryDist.hs
- libraries/Cabal
- libraries/Win32
- libraries/base/src/System/CPUTime/Windows.hsc
- libraries/base/tests/perf/encodingAllocations.hs
- libraries/directory
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/jsbits/errno.js
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/haskeline
- libraries/process
- libraries/unix
- llvm-targets
- m4/fp_cc_supports_target.m4
- m4/fp_setup_windows_toolchain.m4
- m4/fptools_set_platform_vars.m4
- m4/ghc_tables_next_to_code.m4
- rts/StgCRun.c
- rts/linker/PEi386.c
- rts/win32/veh_excn.c
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- + testsuite/tests/parser/should_run/T25937.hs
- + testsuite/tests/parser/should_run/T25937.stdout
- testsuite/tests/parser/should_run/all.T
- + testsuite/tests/parser/should_run/parser_unit_tests.hs
- testsuite/tests/printer/T17697.stderr
- utils/ghc-toolchain/exe/Main.hs
- utils/hsc2hs
- utils/llvm-targets/gen-data-layout.sh
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c31925a1c81d03f5f132b9b37b9a22…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c31925a1c81d03f5f132b9b37b9a22…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T25974] 28 commits: RTS: remove target info and fix host info (#24058)
by Serge S. Gulin (@gulin.serge) 05 May '25
by Serge S. Gulin (@gulin.serge) 05 May '25
05 May '25
Serge S. Gulin pushed to branch wip/T25974 at Glasgow Haskell Compiler / GHC
Commits:
b96e2f77 by Sylvain Henry at 2025-04-18T20:46:33-04:00
RTS: remove target info and fix host info (#24058)
The RTS isn't a compiler, hence it doesn't have a target and we remove
the reported target info displayed by "+RTS --info". We also fix the
host info displayed by "+RTS --info": the host of the RTS is the
RTS-building compiler's target, not the compiler's host (wrong when
doing cross-compilation).
- - - - -
6d9965f4 by Sylvain Henry at 2025-04-18T20:46:33-04:00
RTS: remove build info
As per the discussion in !13967, there is no reason to tag the RTS with
information about the build platform.
- - - - -
d52e9b3f by Vladislav Zavialov at 2025-04-18T20:47:15-04:00
Diagnostics: remove the KindMismatch constructor (#25957)
The KindMismatch constructor was only used as an intermediate
representation in pretty-printing.
Its removal addresses a problem detected by the "codes" test case:
[GHC-89223] is untested (constructor = KindMismatch)
In a concious deviation from the usual procedure, the error code
GHC-89223 is removed entirely rather than marked as Outdated.
The reason is that it never was user-facing in the first place.
- - - - -
e2f2f9d0 by Vladislav Zavialov at 2025-04-20T10:53:39-04:00
Add name for -Wunusable-unpack-pragmas
This warning had no name or flag and was triggered unconditionally.
Now it is part of -Wdefault.
In GHC.Tc.TyCl.tcTyClGroupsPass's strict mode, we now have to
force-enable this warning to ensure that detection of flawed groups
continues to work even if the user disables the warning with the
-Wno-unusable-unpack-pragmas option. Test case: T3990c
Also, the misnamed BackpackUnpackAbstractType is now called
UnusableUnpackPragma.
- - - - -
6caa6508 by Adam Gundry at 2025-04-20T10:54:22-04:00
Fix specialisation of incoherent instances (fixes #25883)
GHC normally assumes that class constraints are canonical, meaning that
the specialiser is allowed to replace one dictionary argument with another
provided that they have the same type. The `-fno-specialise-incoherents`
flag alters INCOHERENT instance definitions so that they will prevent
specialisation in some cases, by inserting `nospec`.
This commit fixes a bug in 7124e4ad76d98f1fc246ada4fd7bf64413ff2f2e, which
treated some INCOHERENT instance matches as if `-fno-specialise-incoherents`
was in effect, thereby unnecessarily preventing specialisation. In addition
it updates the relevant `Note [Rules for instance lookup]` and adds a new
`Note [Canonicity for incoherent matches]`.
- - - - -
0426fd6c by Adam Gundry at 2025-04-20T10:54:23-04:00
Add regression test for #23429
- - - - -
eec96527 by Adam Gundry at 2025-04-20T10:54:23-04:00
user's guide: update specification of overlapping/incoherent instances
The description of the instance resolution algorithm in the user's
guide was slightly out of date, because it mentioned in-scope given
constraints only at the end, whereas the implementation checks for
their presence before any of the other steps.
This also adds a warning to the user's guide about the impact of
incoherent instances on specialisation, and more clearly documents
some of the other effects of `-XIncoherentInstances`.
- - - - -
a00eeaec by Matthew Craven at 2025-04-20T10:55:03-04:00
Fix bytecode generation for `tagToEnum# <LITERAL>`
Fixes #25975.
- - - - -
2e204269 by Andreas Klebinger at 2025-04-22T12:20:41+02:00
Simplifier: Constant fold invald tagToEnum# calls to bottom expr.
When applying tagToEnum# to a out-of-range value it's best to simply
constant fold it to a bottom expression. That potentially allows more
dead code elimination and makes debugging easier.
Fixes #25976
- - - - -
7250fc0c by Matthew Pickering at 2025-04-22T16:24:04-04:00
Move -fno-code note into Downsweep module
This note was left behind when all the code which referred to it was
moved into the GHC.Driver.Downsweep module
- - - - -
d2dc89b4 by Matthew Pickering at 2025-04-22T16:24:04-04:00
Apply editing notes to Note [-fno-code mode] suggested by sheaf
These notes were suggested in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/14241
- - - - -
91564daf by Matthew Pickering at 2025-04-24T00:29:02-04:00
ghci: Use loadInterfaceForModule rather than loadSrcInterface in mkTopLevEnv
loadSrcInterface takes a user given `ModuleName` and resolves it to the
module which needs to be loaded (taking into account module
renaming/visibility etc).
loadInterfaceForModule takes a specific module and loads it.
The modules in `ImpDeclSpec` have already been resolved to the actual
module to get the information from during renaming. Therefore we just
need to fetch the precise interface from disk (and not attempt to rename
it again).
Fixes #25951
- - - - -
2e0c07ab by Simon Peyton Jones at 2025-04-24T00:29:43-04:00
Test for #23298
- - - - -
0eef99b0 by Sven Tennie at 2025-04-24T07:34:36-04:00
RV64: Introduce J instruction (non-local jumps) and don't deallocate stack slots for J_TBL (#25738)
J_TBL result in local jumps, there should not deallocate stack slots
(see Note [extra spill slots].)
J is for non-local jumps, these may need to deallocate stack slots.
- - - - -
1bd3d13e by fendor at 2025-04-24T07:35:17-04:00
Add `UnitId` to `EvalBreakpoint`
The `EvalBreakpoint` is used to communicate that a breakpoint was
encountered during code evaluation.
This `EvalBreakpoint` needs to be converted to an `InternalBreakpointId`
which stores a `Module` to uniquely find the correct `Module` in the
Home Package Table.
The `EvalBreakpoint` used to store only a `ModuleName` which is then
converted to a `Module` based on the currently active home unit.
This is incorrect in the face of multiple home units, the break point
could be in an entirely other home unit!
To fix this, we additionally store the `UnitId` of the `Module` in
`EvalBreakpoint` to later reconstruct the correct `Module`
All of the changes are the consequence of extending `EvalBreakpoint`
with the additional `ShortByteString` of the `UnitId`.
For performance reasons, we store the `ShortByteString` backing the
`UnitId` directly, avoiding marshalling overhead.
- - - - -
fe6ed8d9 by Sylvain Henry at 2025-04-24T18:04:12-04:00
Doc: add doc for JS interruptible calling convention (#24444)
- - - - -
6111c5e4 by Ben Gamari at 2025-04-24T18:04:53-04:00
compiler: Ensure that Panic.Plain.assertPanic' provides callstack
In 36cddd2ce1a3bc62ea8a1307d8bc6006d54109cf @alt-romes removed CallStack
output from `GHC.Utils.Panic.Plain.assertPanic'`. While this output is
redundant due to the exception backtrace proposal, we may be
bootstrapping with a compiler which does not yet include this machinery.
Reintroduce the output for now.
Fixes #25898.
- - - - -
217caad1 by Matthew Pickering at 2025-04-25T18:58:42+01:00
Implement Explicit Level Imports for Template Haskell
This commit introduces the `ExplicitLevelImports` and
`ImplicitStagePersistence` language extensions as proposed in GHC
Proposal #682.
Key Features
------------
- `ExplicitLevelImports` adds two new import modifiers - `splice` and
`quote` - allowing precise control over the level at which imported
identifiers are available
- `ImplicitStagePersistence` (enabled by default) preserves existing
path-based cross-stage persistence behavior
- `NoImplicitStagePersistence` disables implicit cross-stage
persistence, requiring explicit level imports
Benefits
--------
- Improved compilation performance by reducing unnecessary code generation
- Enhanced IDE experience with faster feedback in `-fno-code` mode
- Better dependency tracking by distinguishing compile-time and runtime dependencies
- Foundation for future cross-compilation improvements
This implementation enables the separation of modules needed at
compile-time from those needed at runtime, allowing for more efficient
compilation pipelines and clearer code organization in projects using
Template Haskell.
Implementation Notes
--------------------
The level which a name is availble at is stored in the 'GRE', in the normal
GlobalRdrEnv. The function `greLevels` returns the levels which a specific GRE
is imported at. The level information for a 'Name' is computed by `getCurrentAndBindLevel`.
The level validity is checked by `checkCrossLevelLifting`.
Instances are checked by `checkWellLevelledDFun`, which computes the level an
instance by calling `checkWellLevelledInstanceWhat`, which sees what is
available at by looking at the module graph.
Modifications to downsweep
--------------------------
Code generation is now only enabled for modules which are needed at
compile time.
See the Note [-fno-code mode] for more information.
Uniform error messages for level errors
---------------------------------------
All error messages to do with levels are now reported uniformly using
the `TcRnBadlyStaged` constructor.
Error messages are uniformly reported in terms of levels.
0 - top-level
1 - quote level
-1 - splice level
The only level hard-coded into the compiler is the top-level in
GHC.Types.ThLevelIndex.topLevelIndex.
Uniformly refer to levels and stages
------------------------------------
There was much confusion about levels vs stages in the compiler.
A level is a semantic concept, used by the typechecker to ensure a
program can be evaluated in a well-staged manner.
A stage is an operational construct, program evaluation proceeds in
stages.
Deprecate -Wbadly-staged-types
------------------------------
`-Wbadly-staged-types` is deprecated in favour of `-Wbadly-levelled-types`.
Lift derivation changed
-----------------------
Derived lift instances will now not generate code with expression
quotations.
Before:
```
data A = A Int deriving Lift
=>
lift (A x) = [| A $(lift x) |]
```
After:
```
lift (A x) = conE 'A `appE` (lift x)
```
This is because if you attempt to derive `Lift` in a module where
`NoImplicitStagePersistence` is enabled, you would get an infinite loop
where a constructor was attempted to be persisted using the instance you
are currently defining.
GHC API Changes
---------------
The ModuleGraph now contains additional information about the type of
the edges (normal, quote or splice) between modules. This is abstracted
using the `ModuleGraphEdge` data type.
Fixes #25828
-------------------------
Metric Increase:
MultiLayerModulesTH_Make
-------------------------
- - - - -
7641a74a by Simon Peyton Jones at 2025-04-26T22:05:19-04:00
Get a decent MatchContext for pattern synonym bindings
In particular when we have a pattern binding
K p1 .. pn = rhs
where K is a pattern synonym. (It might be nested.)
This small MR fixes #25995. It's a tiny fix, to an error message,
removing an always-dubious `unkSkol`.
The bug report was in the context of horde-ad, a big program,
and I didn't manage to make a small repro case quickly. I decided
not to bother further.
- - - - -
ce616f49 by Simon Peyton Jones at 2025-04-27T21:10:25+01:00
Fix infelicities in the Specialiser
On the way to #23109 (unary classes) I discovered some infelicities
(or maybe tiny bugs, I forget) in the type-class specialiser.
I also tripped over #25965, an outright bug in the rule matcher
Specifically:
* Refactor: I enhanced `wantCallsFor`, whih previously always said
`True`, to discard calls of class-ops, data constructors etc. This is
a bit more efficient; and it means we don't need to worry about
filtering them out later.
* Fix: I tidied up some tricky logic that eliminated redundant
specialisations. It wasn't working correctly. See the expanded
Note [Specialisations already covered], and
(MP3) in Note [Specialising polymorphic dictionaries].
See also the new top-level `alreadyCovered`
function, which now goes via `GHC.Core.Rules.ruleLhsIsMoreSpecific`
I also added a useful Note [The (CI-KEY) invariant]
* Fix #25965: fixed a tricky bug in the `go_fam_fam` in
`GHC.Core.Unify.uVarOrFam`, which allows matching to succeed
without binding all type varibles.
I enhanced Note [Apartness and type families] some more
* #25703. This ticket "just works" with -fpolymorphic-specialisation;
but I was surprised that it worked! In this MR I added documentation
to Note [Interesting dictionary arguments] to explain; and tests to
ensure it stays fixed.
- - - - -
22d11fa8 by Simon Peyton Jones at 2025-04-28T18:05:19-04:00
Track rewriter sets more accurately in constraint solving
The key change, which fixed #25440, is to call `recordRewriter` in
GHC.Tc.Solver.Rewrite.rewrite_exact_fam_app. This missing call meant
that we were secretly rewriting a Wanted with a Wanted, but not really
noticing; and that led to a very bad error message, as you can see
in the ticket.
But of course that led me into rabbit hole of other refactoring around
the RewriteSet code:
* Improve Notes [Wanteds rewrite Wanteds]
* Zonk the RewriterSet in `zonkCtEvidence` rather than only in GHC.Tc.Errors.
This is tidier anyway (e.g. de-clutters debug output), and helps with the
next point.
* In GHC.Tc.Solver.Equality.inertsCanDischarge, don't replace a constraint
with no rewriters with an equal constraint that has many. See
See (CE4) in Note [Combining equalities]
* Move zonkRewriterSet and friends from GHC.Tc.Zonk.Type into
GHC.Tc.Zonk.TcType, where they properly belong.
A handful of tests get better error messages.
For some reason T24984 gets 12% less compiler allocation -- good
Metric Decrease:
T24984
- - - - -
6467d61e by Brandon Chinn at 2025-04-29T18:36:03-04:00
Fix lexing "\^\" (#25937)
This broke in the refactor in !13128, where the old code parsed escape
codes and collapsed string gaps at the same time, but the new code
collapsed gaps first, then resolved escape codes. The new code used a
naive heuristic to skip escaped backslashes, but didn't account for
"\^\".
- - - - -
99868a86 by Jens Petersen at 2025-04-29T18:36:44-04:00
hadrian: default selftest to disabled
- - - - -
aba2a4a5 by Zubin Duggal at 2025-04-30T06:35:59-04:00
get-win32-tarballs.py: List tarball files to be downloaded if we cannot find them
Fixes #25929
- - - - -
d99a617b by Ben Gamari at 2025-04-30T06:36:40-04:00
Move Data ModuleName instance to Language.Haskell.Syntax.Module.Name
Fixes #25968.
- - - - -
9995c2b7 by Serge S. Gulin at 2025-05-04T17:13:36+03:00
Support for ARM64 Windows (LLVM-enabled) (fixes #24603)
1. Add Windows AArch64 cross-compilation support via CI jobs
Introduce new CI configurations for cross-compiling to Windows ARM64 using Debian12Wine, FEX, and MSYS2.
Configure toolchain variables for LLVM MinGW and Wine emulation in CI pipelines.
2. Adjust compiler and RTS for AArch64 Windows compatibility
Reserve register `x18` on Windows and Darwin platforms in AArch64 codegen.
Handle Windows-specific relocations and data sections in AArch64 assembler.
Update PEi386 linker to recognize ARM64 binaries and support exception handling.
Adjust LLVM target definitions and data layouts for new architectures.
Update `ghc-toolchain` and build scripts to handle `TablesNextToCode` on Windows ARM64.
3. Enhance CI scripts and stability
Modify `ci.sh` to handle mingw cross-targets, fixing GHC executable paths and test execution.
Use `diff -w` in tests to ignore whitespace differences, improving cross-platform consistency.
4. Refactor and clean up code
Remove redundant imports in hello.hs test.
Improve error messages and checks for unsupported configurations in the driver.
Add `EXDEV` error code to `errno.js`.
Add async/sync flags to IO logs at `base.js`.
Improve POSIX compatibility for file close at `base.js`: decrease indeterminism for mixed cases of async and sync code.
5. Update dependencies: `Cabal`, `Win32`, `directory`, `process`, `haskeline`, and `unix`.
submodule
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
Co-authored-by: Dmitrii Egorov <egorov.d.i(a)icloud.com>
Co-authored-by: Andrei Borzenkov <root(a)sandwitch.dev>
- - - - -
50fa8165 by Javran Cheng at 2025-05-05T05:55:39-04:00
Suppress unused do-binding if discarded variable is Any or ZonkAny.
Consider example (#25895):
> do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`.
Nothing constrains `b`, so it will be instantiates with `Any` or
`ZonkAny`.
But we certainly don't want to complain about a discarded do-binding.
Fixes #25895
- - - - -
90e99e9a by Serge S. Gulin at 2025-05-05T19:40:56+03:00
Add Wine support
- - - - -
402 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/hello.hs
- .gitlab/jobs.yaml
- boot
- compiler/CodeGen.Platform.h
- compiler/GHC.hs
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/ByteCode/Asm.hs
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/ByteCode/Types.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/RV64/CodeGen.hs
- compiler/GHC/CmmToAsm/RV64/Instr.hs
- compiler/GHC/CmmToAsm/RV64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs
- compiler/GHC/Core/Coercion.hs
- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Core/Opt/ConstantFold.hs
- compiler/GHC/Core/Opt/Specialise.hs
- compiler/GHC/Core/Rules.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Data/Graph/Directed/Reachability.hs
- compiler/GHC/Driver/Backpack.hs
- compiler/GHC/Driver/Downsweep.hs
- compiler/GHC/Driver/DynFlags.hs
- compiler/GHC/Driver/Flags.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/MakeFile.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/HsToCore/Breakpoints.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/Iface/Recomp.hs
- compiler/GHC/Iface/Tidy.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/Errors/Ppr.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/Header.hs
- compiler/GHC/Parser/Lexer.x
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Parser/String.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Rename/Splice.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Runtime/Eval.hs
- compiler/GHC/Runtime/Interpreter.hs
- compiler/GHC/Runtime/Loader.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Plugin.hs
- compiler/GHC/Tc/Solver/Default.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/Solver/Equality.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Solver/Rewrite.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Types/LclEnv.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Types/TH.hs
- compiler/GHC/Tc/Utils/Backpack.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/Env.hs
- compiler/GHC/Tc/Utils/Monad.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Tc/Zonk/TcType.hs
- compiler/GHC/Tc/Zonk/Type.hs
- compiler/GHC/Types/Basic.hs
- compiler/GHC/Types/Error/Codes.hs
- compiler/GHC/Types/Name/Reader.hs
- + compiler/GHC/Types/ThLevelIndex.hs
- compiler/GHC/Unit/Home/PackageTable.hs
- compiler/GHC/Unit/Module/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs
- compiler/GHC/Unit/Module/Imported.hs
- compiler/GHC/Unit/Module/ModSummary.hs
- + compiler/GHC/Unit/Module/Stage.hs
- compiler/GHC/Unit/Types.hs
- compiler/GHC/Utils/Binary.hs
- compiler/GHC/Utils/Outputable.hs
- compiler/GHC/Utils/Panic/Plain.hs
- compiler/Language/Haskell/Syntax/ImpExp.hs
- + compiler/Language/Haskell/Syntax/ImpExp/IsBoot.hs
- compiler/Language/Haskell/Syntax/Module/Name.hs
- compiler/ghc.cabal.in
- configure.ac
- docs/users_guide/9.14.1-notes.rst
- docs/users_guide/exts/control.rst
- docs/users_guide/exts/instances.rst
- docs/users_guide/exts/template_haskell.rst
- docs/users_guide/javascript.rst
- docs/users_guide/phases.rst
- docs/users_guide/using-warnings.rst
- ghc/GHCi/UI.hs
- hadrian/README.md
- hadrian/hadrian.cabal
- hadrian/src/Builder.hs
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/BinaryDist.hs
- hadrian/src/Settings/Packages.hs
- libraries/Cabal
- libraries/Win32
- libraries/base/src/System/CPUTime/Windows.hsc
- libraries/base/tests/IO/Makefile
- libraries/base/tests/perf/encodingAllocations.hs
- libraries/directory
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/jsbits/errno.js
- libraries/ghc-internal/src/GHC/Internal/Event/Windows.hsc
- libraries/ghc-internal/src/GHC/Internal/LanguageExtensions.hs
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/ghci/GHCi/Message.hs
- libraries/ghci/GHCi/Run.hs
- libraries/haskeline
- libraries/process
- libraries/unix
- llvm-targets
- m4/find_merge_objects.m4
- m4/fp_cc_supports_target.m4
- m4/fp_setup_windows_toolchain.m4
- m4/fptools_set_platform_vars.m4
- m4/ghc_tables_next_to_code.m4
- rts/Exception.cmm
- rts/Interpreter.c
- rts/RtsUtils.c
- rts/StgCRun.c
- rts/linker/PEi386.c
- rts/win32/veh_excn.c
- testsuite/ghc-config/ghc-config.hs
- testsuite/tests/ado/ado004.stderr
- testsuite/tests/annotations/should_fail/annfail03.stderr
- testsuite/tests/annotations/should_fail/annfail04.stderr
- testsuite/tests/annotations/should_fail/annfail06.stderr
- testsuite/tests/annotations/should_fail/annfail09.stderr
- + testsuite/tests/bytecode/T25975.hs
- + testsuite/tests/bytecode/T25975.stdout
- testsuite/tests/bytecode/all.T
- testsuite/tests/count-deps/CountDepsAst.stdout
- testsuite/tests/count-deps/CountDepsParser.stdout
- testsuite/tests/dependent/should_compile/T14729.stderr
- testsuite/tests/dependent/should_compile/T15743.stderr
- testsuite/tests/dependent/should_compile/T15743e.stderr
- testsuite/tests/deriving/should_compile/T14682.stderr
- testsuite/tests/determinism/determ021/determ021.stdout
- testsuite/tests/diagnostic-codes/codes.stdout
- + testsuite/tests/driver/T4437.stdout
- testsuite/tests/driver/json2.stderr
- testsuite/tests/gadt/T19847a.stderr
- + testsuite/tests/gadt/T23298.hs
- + testsuite/tests/gadt/T23298.stderr
- testsuite/tests/gadt/all.T
- testsuite/tests/ghc-api/fixed-nodes/FixedNodes.hs
- testsuite/tests/ghc-api/fixed-nodes/ModuleGraphInvariants.hs
- testsuite/tests/ghc-api/fixed-nodes/all.T
- + testsuite/tests/ghci/scripts/GhciPackageRename.hs
- + testsuite/tests/ghci/scripts/GhciPackageRename.script
- + testsuite/tests/ghci/scripts/GhciPackageRename.stdout
- testsuite/tests/ghci/scripts/all.T
- testsuite/tests/indexed-types/should_compile/T15711.stderr
- testsuite/tests/indexed-types/should_compile/T15852.stderr
- testsuite/tests/indexed-types/should_compile/T3017.stderr
- testsuite/tests/indexed-types/should_fail/T3330c.stderr
- testsuite/tests/indexed-types/should_fail/T4174.stderr
- testsuite/tests/indexed-types/should_fail/T8227.stderr
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/template-haskell-exports.stdout
- testsuite/tests/module/mod185.stderr
- testsuite/tests/parser/should_compile/DumpParsedAst.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/DumpSemis.stderr
- testsuite/tests/parser/should_compile/KindSigs.stderr
- testsuite/tests/parser/should_compile/T14189.stderr
- + testsuite/tests/parser/should_run/T25937.hs
- + testsuite/tests/parser/should_run/T25937.stdout
- testsuite/tests/parser/should_run/all.T
- + testsuite/tests/parser/should_run/parser_unit_tests.hs
- testsuite/tests/partial-sigs/should_compile/ADT.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr1.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr2.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr3.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr4.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr5.stderr
- testsuite/tests/partial-sigs/should_compile/AddAndOr6.stderr
- testsuite/tests/partial-sigs/should_compile/BoolToBool.stderr
- testsuite/tests/partial-sigs/should_compile/DataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting1MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROff.stderr
- testsuite/tests/partial-sigs/should_compile/Defaulting2MROn.stderr
- testsuite/tests/partial-sigs/should_compile/Either.stderr
- testsuite/tests/partial-sigs/should_compile/EqualityConstraint.stderr
- testsuite/tests/partial-sigs/should_compile/Every.stderr
- testsuite/tests/partial-sigs/should_compile/EveryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSig.stderr
- testsuite/tests/partial-sigs/should_compile/ExpressionSigNamed.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints1.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints2.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraConstraints3.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROff.stderr
- testsuite/tests/partial-sigs/should_compile/ExtraNumAMROn.stderr
- testsuite/tests/partial-sigs/should_compile/Forall1.stderr
- testsuite/tests/partial-sigs/should_compile/GenNamed.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank1.stderr
- testsuite/tests/partial-sigs/should_compile/HigherRank2.stderr
- testsuite/tests/partial-sigs/should_compile/LocalDefinitionBug.stderr
- testsuite/tests/partial-sigs/should_compile/Meltdown.stderr
- testsuite/tests/partial-sigs/should_compile/MonoLocalBinds.stderr
- testsuite/tests/partial-sigs/should_compile/NamedTyVar.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInDataFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/NamedWildcardInTypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/ParensAroundContext.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind.stderr
- testsuite/tests/partial-sigs/should_compile/PatBind2.stderr
- testsuite/tests/partial-sigs/should_compile/PatternSig.stderr
- testsuite/tests/partial-sigs/should_compile/Recursive.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcards.stderr
- testsuite/tests/partial-sigs/should_compile/ScopedNamedWildcardsGood.stderr
- testsuite/tests/partial-sigs/should_compile/ShowNamed.stderr
- testsuite/tests/partial-sigs/should_compile/SimpleGen.stderr
- testsuite/tests/partial-sigs/should_compile/SkipMany.stderr
- testsuite/tests/partial-sigs/should_compile/SomethingShowable.stderr
- testsuite/tests/partial-sigs/should_compile/TypeFamilyInstanceLHS.stderr
- testsuite/tests/partial-sigs/should_compile/Uncurry.stderr
- testsuite/tests/partial-sigs/should_compile/UncurryNamed.stderr
- testsuite/tests/partial-sigs/should_compile/WarningWildcardInstantiations.stderr
- testsuite/tests/polykinds/T15592.stderr
- testsuite/tests/polykinds/T15592b.stderr
- testsuite/tests/printer/T17697.stderr
- testsuite/tests/printer/T18052a.stderr
- testsuite/tests/quasiquotation/qq001/qq001.stderr
- testsuite/tests/quasiquotation/qq002/qq002.stderr
- testsuite/tests/quasiquotation/qq003/qq003.stderr
- testsuite/tests/quasiquotation/qq004/qq004.stderr
- + testsuite/tests/quotes/T5721.stderr
- testsuite/tests/roles/should_compile/Roles1.stderr
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles2.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/roles/should_compile/T8958.stderr
- testsuite/tests/showIface/DocsInHiFile1.stdout
- testsuite/tests/showIface/DocsInHiFileTH.stdout
- testsuite/tests/showIface/HaddockIssue849.stdout
- testsuite/tests/showIface/HaddockOpts.stdout
- testsuite/tests/showIface/HaddockSpanIssueT24378.stdout
- testsuite/tests/showIface/LanguageExts.stdout
- testsuite/tests/showIface/MagicHashInHaddocks.stdout
- testsuite/tests/showIface/NoExportList.stdout
- testsuite/tests/showIface/PragmaDocs.stdout
- testsuite/tests/showIface/ReExports.stdout
- testsuite/tests/simplCore/should_compile/Makefile
- testsuite/tests/simplCore/should_compile/T23307c.stderr
- + testsuite/tests/simplCore/should_compile/T25703.hs
- + testsuite/tests/simplCore/should_compile/T25703.stderr
- + testsuite/tests/simplCore/should_compile/T25703a.hs
- + testsuite/tests/simplCore/should_compile/T25703a.stderr
- + testsuite/tests/simplCore/should_compile/T25883.hs
- + testsuite/tests/simplCore/should_compile/T25883.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883b.hs
- + testsuite/tests/simplCore/should_compile/T25883b.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883c.hs
- + testsuite/tests/simplCore/should_compile/T25883c.substr-simpl
- + testsuite/tests/simplCore/should_compile/T25883d.hs
- + testsuite/tests/simplCore/should_compile/T25883d.stderr
- + testsuite/tests/simplCore/should_compile/T25883d_import.hs
- + testsuite/tests/simplCore/should_compile/T25965.hs
- + testsuite/tests/simplCore/should_compile/T25976.hs
- + testsuite/tests/simplCore/should_compile/T3990c.hs
- + testsuite/tests/simplCore/should_compile/T3990c.stdout
- testsuite/tests/simplCore/should_compile/all.T
- testsuite/tests/simplCore/should_fail/T25672.stderr
- + testsuite/tests/simplCore/should_run/T23429.hs
- + testsuite/tests/simplCore/should_run/T23429.stdout
- testsuite/tests/simplCore/should_run/all.T
- + testsuite/tests/splice-imports/ClassA.hs
- + testsuite/tests/splice-imports/InstanceA.hs
- + testsuite/tests/splice-imports/Makefile
- + testsuite/tests/splice-imports/SI01.hs
- + testsuite/tests/splice-imports/SI01A.hs
- + testsuite/tests/splice-imports/SI02.hs
- + testsuite/tests/splice-imports/SI03.hs
- + testsuite/tests/splice-imports/SI03.stderr
- + testsuite/tests/splice-imports/SI04.hs
- + testsuite/tests/splice-imports/SI05.hs
- + testsuite/tests/splice-imports/SI05.stderr
- + testsuite/tests/splice-imports/SI05A.hs
- + testsuite/tests/splice-imports/SI06.hs
- + testsuite/tests/splice-imports/SI07.hs
- + testsuite/tests/splice-imports/SI07.stderr
- + testsuite/tests/splice-imports/SI07A.hs
- + testsuite/tests/splice-imports/SI08.hs
- + testsuite/tests/splice-imports/SI08.stderr
- + testsuite/tests/splice-imports/SI08_oneshot.stderr
- + testsuite/tests/splice-imports/SI09.hs
- + testsuite/tests/splice-imports/SI10.hs
- + testsuite/tests/splice-imports/SI13.hs
- + testsuite/tests/splice-imports/SI14.hs
- + testsuite/tests/splice-imports/SI14.stderr
- + testsuite/tests/splice-imports/SI15.hs
- + testsuite/tests/splice-imports/SI15.stderr
- + testsuite/tests/splice-imports/SI16.hs
- + testsuite/tests/splice-imports/SI16.stderr
- + testsuite/tests/splice-imports/SI17.hs
- + testsuite/tests/splice-imports/SI18.hs
- + testsuite/tests/splice-imports/SI18.stderr
- + testsuite/tests/splice-imports/SI19.hs
- + testsuite/tests/splice-imports/SI19A.hs
- + testsuite/tests/splice-imports/SI20.hs
- + testsuite/tests/splice-imports/SI20.stderr
- + testsuite/tests/splice-imports/SI21.hs
- + testsuite/tests/splice-imports/SI21.stderr
- + testsuite/tests/splice-imports/SI22.hs
- + testsuite/tests/splice-imports/SI22.stderr
- + testsuite/tests/splice-imports/SI23.hs
- + testsuite/tests/splice-imports/SI23A.hs
- + testsuite/tests/splice-imports/SI24.hs
- + testsuite/tests/splice-imports/SI25.hs
- + testsuite/tests/splice-imports/SI25.stderr
- + testsuite/tests/splice-imports/SI25Helper.hs
- + testsuite/tests/splice-imports/SI26.hs
- + testsuite/tests/splice-imports/SI27.hs
- + testsuite/tests/splice-imports/SI27.stderr
- + testsuite/tests/splice-imports/SI28.hs
- + testsuite/tests/splice-imports/SI28.stderr
- + testsuite/tests/splice-imports/SI29.hs
- + testsuite/tests/splice-imports/SI29.stderr
- + testsuite/tests/splice-imports/SI30.script
- + testsuite/tests/splice-imports/SI30.stdout
- + testsuite/tests/splice-imports/SI31.script
- + testsuite/tests/splice-imports/SI31.stderr
- + testsuite/tests/splice-imports/SI32.script
- + testsuite/tests/splice-imports/SI32.stdout
- + testsuite/tests/splice-imports/SI33.script
- + testsuite/tests/splice-imports/SI33.stdout
- + testsuite/tests/splice-imports/SI34.hs
- + testsuite/tests/splice-imports/SI34.stderr
- + testsuite/tests/splice-imports/SI34M1.hs
- + testsuite/tests/splice-imports/SI34M2.hs
- + testsuite/tests/splice-imports/SI35.hs
- + testsuite/tests/splice-imports/SI35A.hs
- + testsuite/tests/splice-imports/SI36.hs
- + testsuite/tests/splice-imports/SI36.stderr
- + testsuite/tests/splice-imports/SI36_A.hs
- + testsuite/tests/splice-imports/SI36_B1.hs
- + testsuite/tests/splice-imports/SI36_B2.hs
- + testsuite/tests/splice-imports/SI36_B3.hs
- + testsuite/tests/splice-imports/SI36_C1.hs
- + testsuite/tests/splice-imports/SI36_C2.hs
- + testsuite/tests/splice-imports/SI36_C3.hs
- + testsuite/tests/splice-imports/all.T
- testsuite/tests/th/T16976z.stderr
- testsuite/tests/th/T17820a.stderr
- testsuite/tests/th/T17820b.stderr
- testsuite/tests/th/T17820c.stderr
- testsuite/tests/th/T17820d.stderr
- testsuite/tests/th/T17820e.stderr
- testsuite/tests/th/T21547.stderr
- testsuite/tests/th/T23829_hasty.stderr
- testsuite/tests/th/T23829_hasty_b.stderr
- testsuite/tests/th/T23829_tardy.ghc.stderr
- testsuite/tests/th/T5795.stderr
- testsuite/tests/th/TH_Roles2.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr
- testsuite/tests/typecheck/should_compile/T18406b.stderr
- testsuite/tests/typecheck/should_compile/T18529.stderr
- testsuite/tests/typecheck/should_compile/T21023.stderr
- testsuite/tests/typecheck/should_compile/T25266a.stderr
- testsuite/tests/typecheck/should_compile/T7050.stderr
- testsuite/tests/typecheck/should_fail/T18851.stderr
- testsuite/tests/typecheck/should_fail/T3966.stderr
- + testsuite/tests/typecheck/should_fail/T3966b.hs
- + testsuite/tests/typecheck/should_fail/T3966b.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/unboxedsums/unpack_sums_5.stderr
- utils/check-exact/ExactPrint.hs
- utils/count-deps/Main.hs
- utils/ghc-toolchain/exe/Main.hs
- utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs
- utils/hsc2hs
- utils/llvm-targets/gen-data-layout.sh
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2f2b7685e6fd13159c0be362cc89fb…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2f2b7685e6fd13159c0be362cc89fb…
You're receiving this email because of your account on gitlab.haskell.org.
1
0

[Git][ghc/ghc][wip/T26004] 7 commits: Fix lexing "\^\" (#25937)
by Simon Peyton Jones (@simonpj) 05 May '25
by Simon Peyton Jones (@simonpj) 05 May '25
05 May '25
Simon Peyton Jones pushed to branch wip/T26004 at Glasgow Haskell Compiler / GHC
Commits:
6467d61e by Brandon Chinn at 2025-04-29T18:36:03-04:00
Fix lexing "\^\" (#25937)
This broke in the refactor in !13128, where the old code parsed escape
codes and collapsed string gaps at the same time, but the new code
collapsed gaps first, then resolved escape codes. The new code used a
naive heuristic to skip escaped backslashes, but didn't account for
"\^\".
- - - - -
99868a86 by Jens Petersen at 2025-04-29T18:36:44-04:00
hadrian: default selftest to disabled
- - - - -
aba2a4a5 by Zubin Duggal at 2025-04-30T06:35:59-04:00
get-win32-tarballs.py: List tarball files to be downloaded if we cannot find them
Fixes #25929
- - - - -
d99a617b by Ben Gamari at 2025-04-30T06:36:40-04:00
Move Data ModuleName instance to Language.Haskell.Syntax.Module.Name
Fixes #25968.
- - - - -
9995c2b7 by Serge S. Gulin at 2025-05-04T17:13:36+03:00
Support for ARM64 Windows (LLVM-enabled) (fixes #24603)
1. Add Windows AArch64 cross-compilation support via CI jobs
Introduce new CI configurations for cross-compiling to Windows ARM64 using Debian12Wine, FEX, and MSYS2.
Configure toolchain variables for LLVM MinGW and Wine emulation in CI pipelines.
2. Adjust compiler and RTS for AArch64 Windows compatibility
Reserve register `x18` on Windows and Darwin platforms in AArch64 codegen.
Handle Windows-specific relocations and data sections in AArch64 assembler.
Update PEi386 linker to recognize ARM64 binaries and support exception handling.
Adjust LLVM target definitions and data layouts for new architectures.
Update `ghc-toolchain` and build scripts to handle `TablesNextToCode` on Windows ARM64.
3. Enhance CI scripts and stability
Modify `ci.sh` to handle mingw cross-targets, fixing GHC executable paths and test execution.
Use `diff -w` in tests to ignore whitespace differences, improving cross-platform consistency.
4. Refactor and clean up code
Remove redundant imports in hello.hs test.
Improve error messages and checks for unsupported configurations in the driver.
Add `EXDEV` error code to `errno.js`.
Add async/sync flags to IO logs at `base.js`.
Improve POSIX compatibility for file close at `base.js`: decrease indeterminism for mixed cases of async and sync code.
5. Update dependencies: `Cabal`, `Win32`, `directory`, `process`, `haskeline`, and `unix`.
submodule
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
Co-authored-by: Dmitrii Egorov <egorov.d.i(a)icloud.com>
Co-authored-by: Andrei Borzenkov <root(a)sandwitch.dev>
- - - - -
50fa8165 by Javran Cheng at 2025-05-05T05:55:39-04:00
Suppress unused do-binding if discarded variable is Any or ZonkAny.
Consider example (#25895):
> do { forever (return ()); blah }
where `forever :: forall a b. IO a -> IO b`.
Nothing constrains `b`, so it will be instantiates with `Any` or
`ZonkAny`.
But we certainly don't want to complain about a discarded do-binding.
Fixes #25895
- - - - -
b4e32a9a by Simon Peyton Jones at 2025-05-05T17:42:05+01:00
Fix a bad untouchability bug im simplifyInfer
This patch addresses #26004. The root cause was that simplifyInfer
was willing to unify variables "far out". The fix, in
runTcSWithEvBinds', is to initialise the inert set given-eq level with
the current level. See
(TGE6) in Note [Tracking Given equalities]
in GHC.Tc.Solver.InertSet
Two loosely related refactors:
* Refactored approximateWCX to return just the free type
variables of the un-quantified constraints. That avoids duplication
of work (these free vars are needed in simplifyInfer) and makes it
clearer that the constraints themselves are irrelevant.
* A little local refactor of TcSMode, which reduces the number of
parameters to runTcSWithEvBinds
- - - - -
61 changed files:
- .gitlab-ci.yml
- .gitlab/ci.sh
- .gitlab/generate-ci/gen_ci.hs
- .gitlab/hello.hs
- .gitlab/jobs.yaml
- compiler/CodeGen.Platform.h
- compiler/GHC/Builtin/Types.hs
- compiler/GHC/CmmToAsm/AArch64/CodeGen.hs
- compiler/GHC/CmmToAsm/AArch64/Instr.hs
- compiler/GHC/CmmToAsm/AArch64/Ppr.hs
- compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs
- compiler/GHC/Driver/Session.hs
- compiler/GHC/HsToCore/Expr.hs
- compiler/GHC/HsToCore/Pmc/Solver/Types.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/String.hs
- compiler/GHC/Platform/Regs.hs
- compiler/GHC/Tc/Solver.hs
- compiler/GHC/Tc/Solver/InertSet.hs
- compiler/GHC/Tc/Solver/Monad.hs
- compiler/GHC/Tc/Types/Constraint.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Unit/Types.hs
- compiler/Language/Haskell/Syntax/Module/Name.hs
- hadrian/README.md
- hadrian/hadrian.cabal
- hadrian/src/Oracles/Setting.hs
- hadrian/src/Rules/BinaryDist.hs
- libraries/Cabal
- libraries/Win32
- libraries/base/src/System/CPUTime/Windows.hsc
- libraries/base/tests/perf/encodingAllocations.hs
- libraries/directory
- libraries/ghc-internal/jsbits/base.js
- libraries/ghc-internal/jsbits/errno.js
- libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs
- libraries/haskeline
- libraries/process
- libraries/unix
- llvm-targets
- m4/fp_cc_supports_target.m4
- m4/fp_setup_windows_toolchain.m4
- m4/fptools_set_platform_vars.m4
- m4/ghc_tables_next_to_code.m4
- rts/StgCRun.c
- rts/linker/PEi386.c
- rts/win32/veh_excn.c
- testsuite/tests/ghc-api/fixed-nodes/all.T
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- + testsuite/tests/parser/should_run/T25937.hs
- + testsuite/tests/parser/should_run/T25937.stdout
- testsuite/tests/parser/should_run/all.T
- + testsuite/tests/parser/should_run/parser_unit_tests.hs
- testsuite/tests/printer/T17697.stderr
- + testsuite/tests/typecheck/should_fail/T26004.hs
- + testsuite/tests/typecheck/should_fail/T26004.stderr
- testsuite/tests/typecheck/should_fail/T7453.stderr
- testsuite/tests/typecheck/should_fail/all.T
- utils/ghc-toolchain/exe/Main.hs
- utils/hsc2hs
- utils/llvm-targets/gen-data-layout.sh
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a070bbb4fd3923da3bdf86b77d3da…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a070bbb4fd3923da3bdf86b77d3da…
You're receiving this email because of your account on gitlab.haskell.org.
1
0