[Git][ghc/ghc] Pushed new branch wip/int-index/imp-exp-whole-namespace
by Vladislav Zavialov (@int-index) 27 Oct '25
by Vladislav Zavialov (@int-index) 27 Oct '25
27 Oct '25
Vladislav Zavialov pushed new branch wip/int-index/imp-exp-whole-namespace at Glasgow Haskell Compiler / GHC
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int-index/imp-exp-whole-names…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/backports-9.14] Add submodules for template-haskell-lift and template-haskell-quasiquoter
by Ben Gamari (@bgamari) 27 Oct '25
by Ben Gamari (@bgamari) 27 Oct '25
27 Oct '25
Ben Gamari pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
Commits:
c514bb16 by Teo Camarasu at 2025-10-27T18:52:10-04:00
Add submodules for template-haskell-lift and template-haskell-quasiquoter
These two new boot libraries expose stable subsets of the
template-haskell interface.
This is an implemenation of the GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/696
Work towards #25262
(cherry picked from commit 4be32153febff94f9c89f7f74971da3721d19c87)
- - - - -
7 changed files:
- .gitmodules
- hadrian/src/Packages.hs
- hadrian/src/Settings/Default.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- + libraries/template-haskell-lift
- + libraries/template-haskell-quasiquoter
Changes:
=====================================
.gitmodules
=====================================
@@ -118,3 +118,9 @@
[submodule "libraries/file-io"]
path = libraries/file-io
url = https://gitlab.haskell.org/ghc/packages/file-io.git
+[submodule "libraries/template-haskell-lift"]
+ path = libraries/template-haskell-lift
+ url = https://gitlab.haskell.org/ghc/template-haskell-lift.git
+[submodule "libraries/template-haskell-quasiquoter"]
+ path = libraries/template-haskell-quasiquoter
+ url = https://gitlab.haskell.org/ghc/template-haskell-quasiquoter.git
=====================================
hadrian/src/Packages.hs
=====================================
@@ -9,7 +9,7 @@ module Packages (
ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline,
hsc2hs, hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy,
libffi, mtl, osString, parsec, pretty, primitive, process, remoteIserv, rts,
- runGhc, semaphoreCompat, stm, templateHaskell, terminfo, text, time, timeout,
+ runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter, terminfo, text, time, timeout,
transformers, unlit, unix, win32, xhtml,
lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace,
ghcPackages, isGhcPackage,
@@ -39,7 +39,7 @@ ghcPackages =
, ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim
, ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline, hsc2hs
, hp2ps, hpc, hpcBin, integerGmp, iserv, libffi, mtl, osString
- , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell
+ , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell, thLift, thQuasiquoter
, terminfo, text, time, transformers, unlit, unix, win32, xhtml, fileio
, timeout
, lintersCommon
@@ -56,7 +56,7 @@ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, count
ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghci, ghcInternal, ghciWrapper, ghcPkg, ghcPrim,
ghcToolchain, ghcToolchainBin, haddockLibrary, haddockApi, haddock, haskeline, hsc2hs,
hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy, remoteIserv, libffi, mtl,
- osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell,
+ osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter,
terminfo, text, time, transformers, unlit, unix, win32, xhtml,
timeout,
lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace
@@ -124,6 +124,8 @@ runGhc = util "runghc"
semaphoreCompat = lib "semaphore-compat"
stm = lib "stm"
templateHaskell = lib "template-haskell"
+thLift = lib "template-haskell-lift"
+thQuasiquoter = lib "template-haskell-quasiquoter"
terminfo = lib "terminfo"
text = lib "text"
time = lib "time"
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -106,6 +106,8 @@ stage0Packages = do
, runGhc
, semaphoreCompat -- depends on
, time -- depends on win32
+ , thLift -- new library not yet present for boot compilers
+ , thQuasiquoter -- new library not yet present for boot compilers
, unlit
, if windowsHost then win32 else unix
-- We must use the in-tree `Win32` as the version
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -20,7 +20,7 @@
-- | This module gives the definition of the 'Lift' class.
--
-- This is an internal module.
--- Please import "Language.Haskell.TH" or "Language.Haskell.TH.Syntax" instead!
+-- Please import "Language.Haskell.TH.Lift", "Language.Haskell.TH" or "Language.Haskell.TH.Syntax" instead!
module GHC.Internal.TH.Lift
( Lift(..)
@@ -70,6 +70,9 @@ import GHC.Internal.ForeignPtr
-- > deriving Lift
--
-- Representation-polymorphic since /template-haskell-2.16.0.0/.
+--
+-- This is exposed both from the @template-haskell-lift@ and @template-haskell@ packages.
+-- Consider importing it from the more stable @template-haskell-lift@ if you don't need the full breadth of the @template-haskell@ interface.
class Lift (t :: TYPE r) where
-- | Turn a value into a Template Haskell expression, suitable for use in
-- a splice.
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
=====================================
@@ -30,6 +30,9 @@ import GHC.Internal.Base hiding (Type)
-- in defining a quasiquoter to be used for expressions, you would
-- define a 'QuasiQuoter' with only 'quoteExp', and leave the other
-- fields stubbed out with errors.
+--
+-- This is exposed both from the @template-haskell-quasiquoter@ and @template-haskell@ packages.
+-- Consider importing it from the more stable @template-haskell-quasiquoter@ if you don't need the full breadth of the @template-haskell@ interface.
data QuasiQuoter = QuasiQuoter {
-- | Quasi-quoter for expressions, invoked by quotes like @lhs = $[q|...]@
quoteExp :: String -> Q Exp,
=====================================
libraries/template-haskell-lift
=====================================
@@ -0,0 +1 @@
+Subproject commit 06c18dfc2d689baabf0e923e3fb9483ac89b8d01
=====================================
libraries/template-haskell-quasiquoter
=====================================
@@ -0,0 +1 @@
+Subproject commit 65246071e82819aa27922c1172861ba346612230
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c514bb1661564d05a0a7b3cdea05b48…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c514bb1661564d05a0a7b3cdea05b48…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/backports-9.14] 3 commits: Fix stack decoding when using profiled runtime
by Ben Gamari (@bgamari) 27 Oct '25
by Ben Gamari (@bgamari) 27 Oct '25
27 Oct '25
Ben Gamari pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC
Commits:
c5e71a10 by Matthew Pickering at 2025-10-27T07:49:45-04:00
Fix stack decoding when using profiled runtime
There are three fixes in this commit.
* We need to replicate the `InfoTable` and `InfoTableProf`
approach for the other stack constants (see the new Stack.ConstantsProf
file).
* Then we need to appropiately import the profiled or non-profiled
versions.
* Finally, there was an incorrect addition in `stackFrameSize`. We need
to cast after performing addition on words.
Fixes #26507
- - - - -
a0fc61dc by fendor at 2025-10-27T07:49:46-04:00
Add regression test for #26507
- - - - -
6cb2ffde by Teo Camarasu at 2025-10-27T18:32:45-04:00
Add submodules for template-haskell-lift and template-haskell-quasiquoter
These two new boot libraries expose stable subsets of the
template-haskell interface.
This is an implemenation of the GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/696
Work towards #25262
(cherry picked from commit 4be32153febff94f9c89f7f74971da3721d19c87)
- - - - -
15 changed files:
- .gitmodules
- hadrian/src/Packages.hs
- hadrian/src/Settings/Default.hs
- libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
- libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
- + libraries/ghc-internal/tests/backtraces/T26507.hs
- + libraries/ghc-internal/tests/backtraces/T26507.stderr
- libraries/ghc-internal/tests/backtraces/all.T
- libraries/ghc-internal/tests/stack-annotation/all.T
- + libraries/template-haskell-lift
- + libraries/template-haskell-quasiquoter
Changes:
=====================================
.gitmodules
=====================================
@@ -118,3 +118,9 @@
[submodule "libraries/file-io"]
path = libraries/file-io
url = https://gitlab.haskell.org/ghc/packages/file-io.git
+[submodule "libraries/template-haskell-lift"]
+ path = libraries/template-haskell-lift
+ url = https://gitlab.haskell.org/ghc/template-haskell-lift.git
+[submodule "libraries/template-haskell-quasiquoter"]
+ path = libraries/template-haskell-quasiquoter
+ url = https://gitlab.haskell.org/ghc/template-haskell-quasiquoter.git
=====================================
hadrian/src/Packages.hs
=====================================
@@ -9,7 +9,7 @@ module Packages (
ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline,
hsc2hs, hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy,
libffi, mtl, osString, parsec, pretty, primitive, process, remoteIserv, rts,
- runGhc, semaphoreCompat, stm, templateHaskell, terminfo, text, time, timeout,
+ runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter, terminfo, text, time, timeout,
transformers, unlit, unix, win32, xhtml,
lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace,
ghcPackages, isGhcPackage,
@@ -39,7 +39,7 @@ ghcPackages =
, ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim
, ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline, hsc2hs
, hp2ps, hpc, hpcBin, integerGmp, iserv, libffi, mtl, osString
- , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell
+ , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell, thLift, thQuasiquoter
, terminfo, text, time, transformers, unlit, unix, win32, xhtml, fileio
, timeout
, lintersCommon
@@ -56,7 +56,7 @@ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, count
ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghci, ghcInternal, ghciWrapper, ghcPkg, ghcPrim,
ghcToolchain, ghcToolchainBin, haddockLibrary, haddockApi, haddock, haskeline, hsc2hs,
hp2ps, hpc, hpcBin, integerGmp, iserv, iservProxy, remoteIserv, libffi, mtl,
- osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell,
+ osString, parsec, pretty, primitive, process, rts, runGhc, semaphoreCompat, stm, templateHaskell, thLift, thQuasiquoter,
terminfo, text, time, transformers, unlit, unix, win32, xhtml,
timeout,
lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace
@@ -124,6 +124,8 @@ runGhc = util "runghc"
semaphoreCompat = lib "semaphore-compat"
stm = lib "stm"
templateHaskell = lib "template-haskell"
+thLift = lib "template-haskell-lift"
+thQuasiquoter = lib "template-haskell-quasiquoter"
terminfo = lib "terminfo"
text = lib "text"
time = lib "time"
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -106,6 +106,8 @@ stage0Packages = do
, runGhc
, semaphoreCompat -- depends on
, time -- depends on win32
+ , thLift -- new library not yet present for boot compilers
+ , thQuasiquoter -- new library not yet present for boot compilers
, unlit
, if windowsHost then win32 else unix
-- We must use the in-tree `Win32` as the version
=====================================
libraries/ghc-internal/cbits/Stack_c.c
=====================================
@@ -9,13 +9,13 @@
#include "rts/storage/InfoTables.h"
StgWord stackFrameSize(StgStack *stack, StgWord offset) {
- StgClosure *c = (StgClosure *)stack->sp + offset;
+ StgClosure *c = (StgClosure *)(stack->sp + offset);
ASSERT(LOOKS_LIKE_CLOSURE_PTR(c));
return stack_frame_sizeW(c);
}
StgStack *getUnderflowFrameStack(StgStack *stack, StgWord offset) {
- StgClosure *frame = (StgClosure *)stack->sp + offset;
+ StgClosure *frame = (StgClosure *)(stack->sp + offset);
ASSERT(LOOKS_LIKE_CLOSURE_PTR(frame));
const StgRetInfoTable *info = get_ret_itbl((StgClosure *)frame);
=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -300,6 +300,7 @@ Library
GHC.Internal.Stack.CCS
GHC.Internal.Stack.CloneStack
GHC.Internal.Stack.Constants
+ GHC.Internal.Stack.ConstantsProf
GHC.Internal.Stack.Decode
GHC.Internal.Stack.Types
GHC.Internal.Stats
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
=====================================
@@ -0,0 +1,140 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module GHC.Internal.Stack.ConstantsProf where
+
+import GHC.Internal.Base
+import GHC.Internal.Enum
+import GHC.Internal.Num
+import GHC.Internal.Show
+import GHC.Internal.Real
+
+-- This file is a copy of GHC.Internal.Stack.Constants, but compiled with PROFILING
+-- defined, since hsc is only invoked once per build in the vanilla way.
+--
+-- Also see GHC.Internal.Heap.InfoTable{Prof}
+#define PROFILING
+#include "Rts.h"
+#undef BLOCK_SIZE
+#undef MBLOCK_SIZE
+#undef BLOCKS_PER_MBLOCK
+#include "DerivedConstants.h"
+
+newtype ByteOffset = ByteOffset { offsetInBytes :: Int }
+ deriving newtype (Eq, Show, Integral, Real, Num, Enum, Ord)
+
+newtype WordOffset = WordOffset { offsetInWords :: Int }
+ deriving newtype (Eq, Show, Integral, Real, Num, Enum, Ord)
+
+offsetStgCatchFrameHandler :: WordOffset
+offsetStgCatchFrameHandler = byteOffsetToWordOffset $
+ (#const OFFSET_StgCatchFrame_handler) + (#size StgHeader)
+
+sizeStgCatchFrame :: Int
+sizeStgCatchFrame = bytesToWords $
+ (#const SIZEOF_StgCatchFrame_NoHdr) + (#size StgHeader)
+
+offsetStgCatchSTMFrameCode :: WordOffset
+offsetStgCatchSTMFrameCode = byteOffsetToWordOffset $
+ (#const OFFSET_StgCatchSTMFrame_code) + (#size StgHeader)
+
+offsetStgCatchSTMFrameHandler :: WordOffset
+offsetStgCatchSTMFrameHandler = byteOffsetToWordOffset $
+ (#const OFFSET_StgCatchSTMFrame_handler) + (#size StgHeader)
+
+sizeStgCatchSTMFrame :: Int
+sizeStgCatchSTMFrame = bytesToWords $
+ (#const SIZEOF_StgCatchSTMFrame_NoHdr) + (#size StgHeader)
+
+offsetStgUpdateFrameUpdatee :: WordOffset
+offsetStgUpdateFrameUpdatee = byteOffsetToWordOffset $
+ (#const OFFSET_StgUpdateFrame_updatee) + (#size StgHeader)
+
+sizeStgUpdateFrame :: Int
+sizeStgUpdateFrame = bytesToWords $
+ (#const SIZEOF_StgUpdateFrame_NoHdr) + (#size StgHeader)
+
+offsetStgAtomicallyFrameCode :: WordOffset
+offsetStgAtomicallyFrameCode = byteOffsetToWordOffset $
+ (#const OFFSET_StgAtomicallyFrame_code) + (#size StgHeader)
+
+offsetStgAtomicallyFrameResult :: WordOffset
+offsetStgAtomicallyFrameResult = byteOffsetToWordOffset $
+ (#const OFFSET_StgAtomicallyFrame_result) + (#size StgHeader)
+
+sizeStgAtomicallyFrame :: Int
+sizeStgAtomicallyFrame = bytesToWords $
+ (#const SIZEOF_StgAtomicallyFrame_NoHdr) + (#size StgHeader)
+
+offsetStgCatchRetryFrameRunningAltCode :: WordOffset
+offsetStgCatchRetryFrameRunningAltCode = byteOffsetToWordOffset $
+ (#const OFFSET_StgCatchRetryFrame_running_alt_code) + (#size StgHeader)
+
+offsetStgCatchRetryFrameRunningFirstCode :: WordOffset
+offsetStgCatchRetryFrameRunningFirstCode = byteOffsetToWordOffset $
+ (#const OFFSET_StgCatchRetryFrame_first_code) + (#size StgHeader)
+
+offsetStgCatchRetryFrameAltCode :: WordOffset
+offsetStgCatchRetryFrameAltCode = byteOffsetToWordOffset $
+ (#const OFFSET_StgCatchRetryFrame_alt_code) + (#size StgHeader)
+
+sizeStgCatchRetryFrame :: Int
+sizeStgCatchRetryFrame = bytesToWords $
+ (#const SIZEOF_StgCatchRetryFrame_NoHdr) + (#size StgHeader)
+
+offsetStgRetFunFrameSize :: WordOffset
+-- StgRetFun has no header, but only a pointer to the info table at the beginning.
+offsetStgRetFunFrameSize = byteOffsetToWordOffset (#const OFFSET_StgRetFun_size)
+
+offsetStgRetFunFrameFun :: WordOffset
+offsetStgRetFunFrameFun = byteOffsetToWordOffset (#const OFFSET_StgRetFun_fun)
+
+offsetStgRetFunFramePayload :: WordOffset
+offsetStgRetFunFramePayload = byteOffsetToWordOffset (#const OFFSET_StgRetFun_payload)
+
+sizeStgRetFunFrame :: Int
+sizeStgRetFunFrame = bytesToWords (#const SIZEOF_StgRetFun)
+
+sizeStgAnnFrame :: Int
+sizeStgAnnFrame = bytesToWords $
+ (#const SIZEOF_StgAnnFrame_NoHdr) + (#size StgHeader)
+
+offsetStgAnnFrameAnn :: WordOffset
+offsetStgAnnFrameAnn = byteOffsetToWordOffset $
+ (#const OFFSET_StgAnnFrame_ann) + (#size StgHeader)
+
+offsetStgBCOFrameInstrs :: ByteOffset
+offsetStgBCOFrameInstrs = (#const OFFSET_StgBCO_instrs) + (#size StgHeader)
+
+offsetStgBCOFrameLiterals :: ByteOffset
+offsetStgBCOFrameLiterals = (#const OFFSET_StgBCO_literals) + (#size StgHeader)
+
+offsetStgBCOFramePtrs :: ByteOffset
+offsetStgBCOFramePtrs = (#const OFFSET_StgBCO_ptrs) + (#size StgHeader)
+
+offsetStgBCOFrameArity :: ByteOffset
+offsetStgBCOFrameArity = (#const OFFSET_StgBCO_arity) + (#size StgHeader)
+
+offsetStgBCOFrameSize :: ByteOffset
+offsetStgBCOFrameSize = (#const OFFSET_StgBCO_size) + (#size StgHeader)
+
+offsetStgClosurePayload :: WordOffset
+offsetStgClosurePayload = byteOffsetToWordOffset $
+ (#const OFFSET_StgClosure_payload) + (#size StgHeader)
+
+sizeStgClosure :: Int
+sizeStgClosure = bytesToWords (#size StgHeader)
+
+byteOffsetToWordOffset :: ByteOffset -> WordOffset
+byteOffsetToWordOffset = WordOffset . bytesToWords . fromInteger . toInteger
+
+bytesToWords :: Int -> Int
+bytesToWords b =
+ if b `mod` bytesInWord == 0 then
+ fromIntegral $ b `div` bytesInWord
+ else
+ error "Unexpected struct alignment!"
+
+bytesInWord :: Int
+bytesInWord = (#const SIZEOF_VOID_P)
+
=====================================
libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
=====================================
@@ -54,9 +54,19 @@ import GHC.Internal.Heap.Closures
GenStackField(..)
)
import GHC.Internal.Heap.Constants (wORD_SIZE_IN_BITS)
-import GHC.Internal.Heap.InfoTable
import GHC.Internal.Stack.Annotation
+-- See Note [No way-dependent imports]
+#if defined(PROFILING)
+import GHC.Internal.Stack.Constants ()
+import GHC.Internal.Stack.ConstantsProf
+import GHC.Internal.Heap.InfoTable ()
+import GHC.Internal.Heap.InfoTableProf
+#else
+import GHC.Internal.Heap.InfoTable
+import GHC.Internal.Heap.InfoTableProf ()
import GHC.Internal.Stack.Constants
+import GHC.Internal.Stack.ConstantsProf ()
+#endif
import GHC.Internal.Stack.CloneStack
import GHC.Internal.InfoProv.Types (InfoProv (..), ipLoc, lookupIPE)
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs
=====================================
@@ -20,7 +20,7 @@
-- | This module gives the definition of the 'Lift' class.
--
-- This is an internal module.
--- Please import "Language.Haskell.TH" or "Language.Haskell.TH.Syntax" instead!
+-- Please import "Language.Haskell.TH.Lift", "Language.Haskell.TH" or "Language.Haskell.TH.Syntax" instead!
module GHC.Internal.TH.Lift
( Lift(..)
@@ -70,6 +70,9 @@ import GHC.Internal.ForeignPtr
-- > deriving Lift
--
-- Representation-polymorphic since /template-haskell-2.16.0.0/.
+--
+-- This is exposed both from the @template-haskell-lift@ and @template-haskell@ packages.
+-- Consider importing it from the more stable @template-haskell-lift@ if you don't need the full breadth of the @template-haskell@ interface.
class Lift (t :: TYPE r) where
-- | Turn a value into a Template Haskell expression, suitable for use in
-- a splice.
=====================================
libraries/ghc-internal/src/GHC/Internal/TH/Quote.hs
=====================================
@@ -30,6 +30,9 @@ import GHC.Internal.Base hiding (Type)
-- in defining a quasiquoter to be used for expressions, you would
-- define a 'QuasiQuoter' with only 'quoteExp', and leave the other
-- fields stubbed out with errors.
+--
+-- This is exposed both from the @template-haskell-quasiquoter@ and @template-haskell@ packages.
+-- Consider importing it from the more stable @template-haskell-quasiquoter@ if you don't need the full breadth of the @template-haskell@ interface.
data QuasiQuoter = QuasiQuoter {
-- | Quasi-quoter for expressions, invoked by quotes like @lhs = $[q|...]@
quoteExp :: String -> Q Exp,
=====================================
libraries/ghc-internal/tests/backtraces/T26507.hs
=====================================
@@ -0,0 +1,7 @@
+import GHC.Internal.Control.Exception
+import GHC.Internal.Exception.Backtrace
+
+main :: IO ()
+main = do
+ setBacktraceMechanismState IPEBacktrace True
+ throwIO $ ErrorCall "Throw error"
=====================================
libraries/ghc-internal/tests/backtraces/T26507.stderr
=====================================
@@ -0,0 +1,8 @@
+T26507: Uncaught exception ghc-internal:GHC.Internal.Exception.ErrorCall:
+
+Throw error
+
+IPE backtrace:
+HasCallStack backtrace:
+ throwIO, called at T26507.hs:7:3 in main:Main
+
=====================================
libraries/ghc-internal/tests/backtraces/all.T
=====================================
@@ -1,2 +1,6 @@
test('T14532a', [], compile_and_run, [''])
test('T14532b', [], compile_and_run, [''])
+test('T26507', [ when(have_profiling(), extra_ways(['prof']))
+ , when(js_arch(), skip)
+ , exit_code(1)], compile_and_run, [''])
+
=====================================
libraries/ghc-internal/tests/stack-annotation/all.T
=====================================
@@ -1,7 +1,10 @@
# Javascript backend don't support annotation frames, yet
-setTestOpts(when(js_arch(), skip))
+# and test with profiling way if available (#26507)
+ann_frame_opts = [ when(js_arch(), skip)
+ , when(have_profiling(), extra_ways(['prof']))
+ , extra_files(['TestUtils.hs'])]
-test('ann_frame001', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
-test('ann_frame002', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
-test('ann_frame003', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
-test('ann_frame004', [extra_files(['TestUtils.hs'])], compile_and_run, [''])
+test('ann_frame001', ann_frame_opts, compile_and_run, [''])
+test('ann_frame002', ann_frame_opts, compile_and_run, [''])
+test('ann_frame003', ann_frame_opts, compile_and_run, [''])
+test('ann_frame004', ann_frame_opts, compile_and_run, [''])
=====================================
libraries/template-haskell-lift
=====================================
@@ -0,0 +1 @@
+Subproject commit 2b63f282bee11fec5aa68a18c535afbe8212165a
=====================================
libraries/template-haskell-quasiquoter
=====================================
@@ -0,0 +1 @@
+Subproject commit 615e73cae78eade99684b562215d1e5af30fb3ee
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3dad0b2486ea3b8cc94d326700ee17…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3dad0b2486ea3b8cc94d326700ee17…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
Ben Gamari deleted branch wip/backports-9.14-2 at Glasgow Haskell Compiler / GHC
--
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][ghc-9.14] 27 commits: haddock: Bump version to 2.33.0
by Ben Gamari (@bgamari) 27 Oct '25
by Ben Gamari (@bgamari) 27 Oct '25
27 Oct '25
Ben Gamari pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
028313ed by Ben Gamari at 2025-10-25T15:18:43-04:00
haddock: Bump version to 2.33.0
- - - - -
61dcd182 by Julian Ospald at 2025-10-25T15:18:43-04:00
Improve error handling in 'getPackageArchives'
When the library dirs in the package conf files are not set up correctly,
the JS linker will happily ignore such packages and not link against them,
although they're part of the link plan.
Fixes #26383
(cherry picked from commit 91b6be10bd58c2bfc1c7c22e81b06ab3be583228)
- - - - -
7bec4f4e by Cheng Shao at 2025-10-25T15:18:43-04:00
rts: fix wasm JSFFI initialization constructor code
This commit fixes wasm JSFFI initialization constructor code so that
the constructor is self-contained and avoids invoking a fake
__main_argc_argv function. The previous approach of reusing
__main_void logic in wasi-libc saves a tiny bit of code, at the
expense of link-time trouble whenever GHC links a wasm module without
-no-hs-main, in which case the driver-generated main function would
clash with the definition here, resulting in a linker error. It's
simply better to avoid messing with the main function, and it would
additionally allow linking wasm32-wasi command modules that does make
use of synchronous JSFFI.
(cherry picked from commit bdc9d130a838017f863f5c7a380cb0858035f859)
- - - - -
b630e81d by Rodrigo Mesquita at 2025-10-25T15:18:43-04:00
Move code-gen aux symbols from ghc-internal to rts
These symbols were all previously defined in ghc-internal and made the
dependency structure awkward, where the rts may refer to some of these
symbols and had to work around that circular dependency the way
described in #26166.
Moreover, the code generator will produce code that uses these symbols!
Therefore, they should be available in the rts:
PRINCIPLE: If the code generator may produce code which uses this
symbol, then it should be defined in the rts rather than, say,
ghc-internal.
That said, the main motivation is towards fixing #26166.
Towards #26166. Pre-requisite of !14892
(cherry picked from commit ba3e5bddb222008591edb6c3d433d93084170571)
- - - - -
6b370222 by Ben Gamari at 2025-10-25T15:18:44-04:00
compiler: Rename isMathFun -> isLibcFun
This set includes more than just math functions.
(cherry picked from commit 43fdfddc25c36ef4811941231d5755bad065796d)
- - - - -
64744873 by Ben Gamari at 2025-10-25T15:18:44-04:00
compiler: Add libc allocator functions to libc_funs
Prototypes for these are now visible from `Prim.h`, resulting in
multiple-declaration warnings in the unregisterised job.
(cherry picked from commit 4ed5138f7af532731f88380f98103487a9f15c5a)
- - - - -
c9301893 by Ben Gamari at 2025-10-25T15:18:44-04:00
rts: Minimize header dependencies of Prim.h
Otherwise we will end up with redundant and incompatible declarations
resulting in warnings during the unregisterised build.
(cherry picked from commit 9a0a076b80d6fb68d7722d2bb72c17c90ba22cd1)
- - - - -
99f980ac by Ben Gamari at 2025-10-25T15:18:44-04:00
rts: Avoid static symbol references to ghc-internal
This resolves #26166, a bug due to new constraints placed by Apple's
linker on undefined references.
One source of such references in the RTS is the many symbols referenced
in ghc-internal. To mitigate #26166, we make these references dynamic,
as described in Note [RTS/ghc-internal interface].
Fixes #26166
Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita(a)gmail.com>
Co-authored-by: Cheng Shao <terrorjack(a)type.dance>
(cherry picked from commit f31de2a9c2405d6645998460e4b501f9279606b3)
- - - - -
7f627345 by fendor at 2025-10-25T15:18:44-04:00
Fix typos in haddock documentation for stack annotation API
(cherry picked from commit e17dc695bf1f5fc015c2a9ab8981ac64d27a3708)
- - - - -
ffd03d32 by Cheng Shao at 2025-10-25T16:12:45-04:00
testsuite: fix T3586 for non-SSE3 platforms
`T3586.hs` contains `-fvia-C -optc-msse3` which I think is a
best-effort basis to harvest the C compiler's auto vectorization
optimizations via the C backend back when the test was added. The
`-fvia-C` part is now a deprecated no-op because GHC can't fall back
to the C backend on a non-unregisterised build, and `-optc-msse3`
might actually cause the test to fail on non x86/x64 platforms, e.g.
recent builds of wasi-sdk would report `wasm32-wasi-clang: error:
unsupported option '-msse3' for target 'wasm32-unknown-wasi'`.
So this patch cleans up this historical cruft. `-fvia-C` is removed,
and `-optc-msse3` is only passed when cpuid contains `pni` (which
indicates support of SSE3).
(cherry picked from commit 70ee825a516bcf7aac762bfedb4a017d35f8dcf3)
- - - - -
0a01bea2 by Ben Gamari at 2025-10-25T16:12:45-04:00
rts/nonmoving: Fix comment spelling
(cherry picked from commit 14281a22eb27498886def8e5d17797c9ce62f3ad)
- - - - -
836511fe by Ben Gamari at 2025-10-25T16:12:45-04:00
rts/nonmoving: Use atomic operations to update bd->flags
(cherry picked from commit bedd38b01d6b113cb3bd10b5d784c16b32efb5bb)
- - - - -
5a50298b by Ben Gamari at 2025-10-25T16:12:45-04:00
nonmoving: Use get_itbl instead of explicit loads
This is cleaner and also fixes unnecessary (and unsound) use of
`volatile`.
(cherry picked from commit 215d68414020dc4ed0636508c9eecd9f44f62168)
- - - - -
1cfaf40a by Ben Gamari at 2025-10-25T16:12:45-04:00
rts/Scav: Handle WHITEHOLEs in scavenge_one
`scavenge_one`, used to scavenge mutable list entries, may encounter
`WHITEHOLE`s when the non-moving GC is in use via two paths:
1. when an MVAR is being marked concurrently
2. when the object belongs to a chain of selectors being short-cutted.
Fixes #26204.
(cherry picked from commit 2c94aa3aa87c14b1ff5c4355c9a90efedd5d10f4)
- - - - -
d4db67c0 by Ben Gamari at 2025-10-25T16:12:45-04:00
gitlab-ci: Make RELEASE_JOB an input
Rather than an undocumented variable.
(cherry picked from commit f9790ca81deb8b14ff2eabf701aecbcfd6501963)
- - - - -
e3ca15f7 by Julian Ospald at 2025-10-25T16:12:45-04:00
ghc-toolchain: Drop `ld.gold` from merge object command
It's deprecated.
Also see #25716
(cherry picked from commit c58f9a615f05e9d43629f6e846ae22cad2a6163d)
- - - - -
5c820b10 by Ben Gamari at 2025-10-25T16:12:45-04:00
rts/posix: Enforce iteration limit on heap reservation logic
Previously we could loop indefinitely when attempting to get an address
space reservation for our heap. Limit the logic to 8 iterations to
ensure we instead issue a reasonable error message.
Addresses #26151.
(cherry picked from commit ff1650c96c61af02e193854312a9ccd303968e47)
- - - - -
1fb72cf5 by Ben Gamari at 2025-10-25T16:12:45-04:00
rts/posix: Hold on to low reservations when reserving heap
Previously when the OS gave us an address space reservation in low
memory we would immediately release it and try again. However, on some
platforms this meant that we would get the same allocation again in the
next iteration (since mmap's `hint` argument is just that, a hint).
Instead we now hold on to low reservations until we have found a
suitable heap reservation.
Fixes #26151.
(cherry picked from commit 0184455728f841a699648f879fdb29128081fc6b)
- - - - -
10bda05d by Luite Stegeman at 2025-10-25T16:12:45-04:00
rts: Fix lost wakeups in threadPaused for threads blocked on black holes
The lazy blackholing code in threadPaused could overwrite closures
that were already eagerly blackholed, and as such wouldn't have a
marked update frame. If the black hole was overwritten by its
original owner, this would lead to an undetected collision, and
the contents of any existing blocking queue being lost.
This adds a check for eagerly blackholed closures and avoids
overwriting their contents.
Fixes #26324
(cherry picked from commit a1de535f762bc23d4cf23a5b1853591dda12cdc9)
- - - - -
a62540e4 by Luite Stegeman at 2025-10-25T16:12:45-04:00
rts: push the correct update frame in stg_AP_STACK
The frame contains an eager black hole (__stg_EAGER_BLACKHOLE_info) so
we should push an stg_bh_upd_frame_info instead of an stg_upd_frame_info.
(cherry picked from commit b7e21e498d39e0ee764e3237544b4c39ddf98467)
- - - - -
d44e8dbe by sheaf at 2025-10-25T16:12:45-04:00
Improve deep subsumption
This commit improves the DeepSubsumption sub-typing implementation
in GHC.Tc.Utils.Unify.tc_sub_type_deep by being less eager to fall back
to unification.
For example, we now are properly able to prove the subtyping relationship
((∀ a. a->a) -> Int) -> Bool <= β[tau] Bool
for an unfilled metavariable β. In this case (with an AppTy on the right),
we used to fall back to unification. No longer: now, given that the LHS
is a FunTy and that the RHS is a deep rho type (does not need any instantiation),
we try to make the RHS into a FunTy, viz.
β := (->) γ
We can then continue using covariance & contravariance of the function
arrow, which allows us to prove the subtyping relationship, instead of
trying to unify which would cause us to error out with:
Couldn't match expected type ‘β’ with actual type ‘(->) ((∀ a. a -> a) -> Int)
See Note [FunTy vs non-FunTy case in tc_sub_type_deep] in GHC.Tc.Utils.Unify.
The other main improvement in this patch concerns type inference.
The main subsumption logic happens (before & after this patch) in
GHC.Tc.Gen.App.checkResultTy. However, before this patch, all of the
DeepSubsumption logic only kicked in in 'check' mode, not in 'infer' mode.
This patch adds deep instantiation in the 'infer' mode of checkResultTy
when we are doing deep subsumption, which allows us to accept programs
such as:
f :: Int -> (forall a. a->a)
g :: Int -> Bool -> Bool
test1 b =
case b of
True -> f
False -> g
test2 b =
case b of
True -> g
False -> f
See Note [Deeply instantiate in checkResultTy when inferring].
Finally, we add representation-polymorphism checks to ensure that the
lambda abstractions we introduce when doing subsumption obey the
representation polymorphism invariants of Note [Representation polymorphism invariants]
in GHC.Core. See Note [FunTy vs FunTy case in tc_sub_type_deep].
This is accompanied by a courtesy change to `(<.>) :: HsWrapper -> HsWrapper -> HsWrapper`,
adding the equation:
WpCast c1 <.> WpCast c2 = WpCast (c1 `mkTransCo` c2)
This is useful because mkWpFun does not introduce an eta-expansion when
both of the argument & result wrappers are casts; so this change allows
us to avoid introducing lambda abstractions when casts suffice.
Fixes #26225
(cherry picked from commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1)
- - - - -
9b42551e by Simon Peyton Jones at 2025-10-25T16:12:46-04:00
Fix deep subsumption again
This commit fixed #26255:
commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1
Author: sheaf <sam.derbyshire(a)gmail.com>
Date: Mon Aug 11 15:50:47 2025 +0200
Improve deep subsumption
This commit improves the DeepSubsumption sub-typing implementation
in GHC.Tc.Utils.Unify.tc_sub_type_deep by being less eager to fall back
to unification.
But alas it still wasn't quite right for view patterns: #26331
This MR does a generalisation to fix it. A bit of a sledgehammer to crack
a nut, but nice.
* Add a field `ir_inst :: InferInstFlag` to `InferResult`, where
```
data InferInstFlag = IIF_Sigma | IIF_ShallowRho | IIF_DeepRho
```
* The flag says exactly how much `fillInferResult` should instantiate
before filling the hole.
* We can also use this to replace the previous very ad-hoc `tcInferSigma`
that was used to implement GHCi's `:type` command.
(cherry picked from commit 716274a5b6c35d963091f563c98d07e72ee4d755)
- - - - -
6c0409bc by sheaf at 2025-10-25T16:12:46-04:00
Use tcMkScaledFunTys in matchExpectedFunTys
We should use tcMkScaledFunTys rather than mkScaledFunTys in
GHC.Tc.Utils.Unify.matchExpectedFunTys, as the latter crashes
when the kind of the result type is a bare metavariable.
We know the result is always Type-like, so we don't need scaledFunTys
to try to rediscover that from the kind.
Fixes #26277
(cherry picked from commit 624afa4a65caa8ec23f85e70574dfb606f90c173)
- - - - -
1e5a7d25 by sheaf at 2025-10-25T16:12:46-04:00
Deep subsumption: unify mults without tcEqMult
As seen in #26332, we may well end up with a non-reflexive multiplicity
coercion when doing deep subsumption. We should do the same thing that
we do without deep subsumption: unify the multiplicities normally,
without requiring that the coercion is reflexive (which is what
'tcEqMult' was doing).
Fixes #26332
(cherry picked from commit dc79593d4606e5cea93e742a9f2def53705bc773)
- - - - -
02e4586a by Ben Gamari at 2025-10-27T07:40:16-04:00
Bump unix to 2.8.8.0
- - - - -
c5e71a10 by Matthew Pickering at 2025-10-27T07:49:45-04:00
Fix stack decoding when using profiled runtime
There are three fixes in this commit.
* We need to replicate the `InfoTable` and `InfoTableProf`
approach for the other stack constants (see the new Stack.ConstantsProf
file).
* Then we need to appropiately import the profiled or non-profiled
versions.
* Finally, there was an incorrect addition in `stackFrameSize`. We need
to cast after performing addition on words.
Fixes #26507
- - - - -
a0fc61dc by fendor at 2025-10-27T07:49:46-04:00
Add regression test for #26507
- - - - -
117 changed files:
- .gitlab-ci.yml
- compiler/GHC/Builtin/PrimOps/Ids.hs
- compiler/GHC/Cmm/CLabel.hs
- compiler/GHC/Cmm/Parser.y
- compiler/GHC/CmmToAsm/Wasm/FromCmm.hs
- compiler/GHC/CmmToC.hs
- compiler/GHC/HsToCore.hs
- compiler/GHC/HsToCore/Foreign/C.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/Linker/Dynamic.hs
- compiler/GHC/Linker/Static.hs
- compiler/GHC/StgToJS/Linker/Linker.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Expr.hs-boot
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/HsType.hs
- compiler/GHC/Tc/Gen/Match.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/Module.hs
- compiler/GHC/Tc/Types/Evidence.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Concrete.hs
- compiler/GHC/Tc/Utils/TcMType.hs
- compiler/GHC/Tc/Utils/TcType.hs
- compiler/GHC/Tc/Utils/Unify.hs
- compiler/GHC/Types/Id/Make.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-experimental/src/GHC/Stack/Annotation/Experimental.hs
- + libraries/ghc-internal/cbits/RtsIface.c
- libraries/ghc-internal/cbits/Stack_c.c
- libraries/ghc-internal/ghc-internal.cabal.in
- + libraries/ghc-internal/include/RtsIfaceSymbols.h
- + libraries/ghc-internal/src/GHC/Internal/Stack/ConstantsProf.hsc
- libraries/ghc-internal/src/GHC/Internal/Stack/Decode.hs
- + libraries/ghc-internal/tests/backtraces/T26507.hs
- + libraries/ghc-internal/tests/backtraces/T26507.stderr
- libraries/ghc-internal/tests/backtraces/all.T
- libraries/ghc-internal/tests/stack-annotation/all.T
- libraries/unix
- rts/Apply.cmm
- rts/BuiltinClosures.c
- rts/CloneStack.h
- rts/Compact.cmm
- rts/ContinuationOps.cmm
- rts/Exception.cmm
- rts/Prelude.h
- rts/PrimOps.cmm
- rts/RtsAPI.c
- rts/RtsStartup.c
- rts/RtsSymbols.c
- + rts/RtsToHsIface.c
- rts/StgStdThunks.cmm
- rts/ThreadPaused.c
- rts/configure.ac
- − rts/external-symbols.list.in
- rts/include/Rts.h
- rts/include/RtsAPI.h
- rts/include/Stg.h
- + rts/include/rts/RtsToHsIface.h
- rts/include/rts/Types.h
- rts/include/rts/storage/Block.h
- rts/include/stg/Prim.h
- rts/posix/OSMem.c
- rts/posix/Signals.c
- libraries/ghc-internal/cbits/atomic.c → rts/prim/atomic.c
- libraries/ghc-internal/cbits/bitrev.c → rts/prim/bitrev.c
- libraries/ghc-internal/cbits/bswap.c → rts/prim/bswap.c
- libraries/ghc-internal/cbits/clz.c → rts/prim/clz.c
- libraries/ghc-internal/cbits/ctz.c → rts/prim/ctz.c
- libraries/ghc-internal/cbits/int64x2minmax.c → rts/prim/int64x2minmax.c
- libraries/ghc-internal/cbits/longlong.c → rts/prim/longlong.c
- libraries/ghc-internal/cbits/mulIntMayOflo.c → rts/prim/mulIntMayOflo.c
- libraries/ghc-internal/cbits/pdep.c → rts/prim/pdep.c
- libraries/ghc-internal/cbits/pext.c → rts/prim/pext.c
- libraries/ghc-internal/cbits/popcnt.c → rts/prim/popcnt.c
- libraries/ghc-internal/cbits/vectorQuotRem.c → rts/prim/vectorQuotRem.c
- libraries/ghc-internal/cbits/word2float.c → rts/prim/word2float.c
- − rts/rts.buildinfo.in
- rts/rts.cabal
- rts/sm/NonMoving.c
- rts/sm/NonMovingMark.c
- rts/sm/Scav.c
- rts/wasm/JSFFI.c
- rts/wasm/scheduler.cmm
- rts/win32/libHSghc-internal.def
- testsuite/driver/cpu_features.py
- testsuite/tests/corelint/LintEtaExpand.stderr
- testsuite/tests/indexed-types/should_fail/T5439.stderr
- + testsuite/tests/linear/should_compile/T26332.hs
- testsuite/tests/linear/should_compile/all.T
- testsuite/tests/partial-sigs/should_compile/T10403.stderr
- testsuite/tests/partial-sigs/should_fail/T10615.stderr
- + testsuite/tests/patsyn/should_compile/T26331.hs
- + testsuite/tests/patsyn/should_compile/T26331a.hs
- testsuite/tests/patsyn/should_compile/all.T
- testsuite/tests/perf/should_run/T3586.hs
- testsuite/tests/perf/should_run/all.T
- + testsuite/tests/rep-poly/NoEtaRequired.hs
- testsuite/tests/rep-poly/T21906.stderr
- testsuite/tests/rep-poly/all.T
- + testsuite/tests/typecheck/should_compile/T26225.hs
- + testsuite/tests/typecheck/should_compile/T26225b.hs
- + testsuite/tests/typecheck/should_compile/T26277.hs
- testsuite/tests/typecheck/should_compile/all.T
- − testsuite/tests/typecheck/should_fail/T12563.stderr
- testsuite/tests/typecheck/should_fail/T14618.stderr
- testsuite/tests/typecheck/should_fail/T6022.stderr
- testsuite/tests/typecheck/should_fail/T8883.stderr
- testsuite/tests/typecheck/should_fail/all.T
- testsuite/tests/typecheck/should_fail/tcfail140.stderr
- utils/deriveConstants/Main.hs
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/MergeObjs.hs
- utils/haddock/haddock-api/haddock-api.cabal
- utils/haddock/haddock.cabal
- utils/jsffi/dyld.mjs
The diff was not included because it is too large.
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4656f1d69bdc88cac62707e57e2453…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4656f1d69bdc88cac62707e57e2453…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
27 Oct '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
544b9ec9 by Vladislav Zavialov at 2025-10-27T18:18:06-04:00
Re-export GHC.Hs.Basic from GHC.Hs
Clean up some import sections in GHC by re-exporting GHC.Hs.Basic
from GHC.Hs.
- - - - -
30 changed files:
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/HsToCore/Foreign/Wasm.hs
- compiler/GHC/HsToCore/Quote.hs
- compiler/GHC/HsToCore/Utils.hs
- compiler/GHC/Parser/Errors/Types.hs
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Deriv/Generate.hs
- compiler/GHC/Tc/Deriv/Generics.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/App.hs
- compiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Tc/Gen/Pat.hs
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Validity.hs
- compiler/GHC/ThToHs.hs
- utils/check-exact/ExactPrint.hs
- utils/haddock/haddock-api/src/Haddock/Convert.hs
- utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
- utils/haddock/haddock-api/src/Haddock/Types.hs
Changes:
=====================================
compiler/GHC/Hs.hs
=====================================
@@ -22,6 +22,7 @@ therefore, is almost nothing but re-exporting.
module GHC.Hs (
module Language.Haskell.Syntax,
+ module GHC.Hs.Basic,
module GHC.Hs.Binds,
module GHC.Hs.Decls,
module GHC.Hs.Expr,
@@ -33,7 +34,6 @@ module GHC.Hs (
module GHC.Hs.Doc,
module GHC.Hs.Extension,
module GHC.Parser.Annotation,
- Fixity,
HsModule(..), AnnsModule(..),
HsParsedModule(..), XModulePs(..)
@@ -42,6 +42,7 @@ module GHC.Hs (
-- friends:
import GHC.Prelude
+import GHC.Hs.Basic
import GHC.Hs.Decls
import GHC.Hs.Binds
import GHC.Hs.Expr
@@ -58,7 +59,6 @@ import GHC.Hs.Instances () -- For Data instances
-- others:
import GHC.Utils.Outputable
-import GHC.Types.Fixity ( Fixity )
import GHC.Types.SrcLoc
import GHC.Unit.Module.Warnings
=====================================
compiler/GHC/Hs/Decls.hs
=====================================
@@ -121,11 +121,11 @@ import GHC.Hs.Doc
import GHC.Types.Basic
import GHC.Core.Coercion
+import GHC.Hs.Basic
import GHC.Hs.Extension
import GHC.Parser.Annotation
import GHC.Types.Name
import GHC.Types.Name.Set
-import GHC.Types.Fixity
-- others:
import GHC.Utils.Misc (count)
=====================================
compiler/GHC/HsToCore/Foreign/Wasm.hs
=====================================
@@ -45,7 +45,6 @@ import GHC.Types.Var
import GHC.Unit
import GHC.Utils.Outputable
import GHC.Utils.Panic
-import Language.Haskell.Syntax.Basic
data Synchronicity = Sync | Async
deriving (Eq)
=====================================
compiler/GHC/HsToCore/Quote.hs
=====================================
@@ -79,7 +79,6 @@ import GHC.Types.ForeignCall
import GHC.Types.Var
import GHC.Types.Id
import GHC.Types.SourceText
-import GHC.Types.Fixity
import GHC.Types.TyThing
import GHC.Types.Name hiding( varName, tcName )
import GHC.Types.Name.Env
@@ -89,8 +88,6 @@ import Data.Kind (Constraint)
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Data.ByteString ( unpack )
import Control.Monad
import Data.List (sort, sortBy)
=====================================
compiler/GHC/HsToCore/Utils.hs
=====================================
@@ -45,8 +45,6 @@ module GHC.HsToCore.Utils (
import GHC.Prelude
-import Language.Haskell.Syntax.Basic (Boxity(..))
-
import {-# SOURCE #-} GHC.HsToCore.Match ( matchSimply )
import {-# SOURCE #-} GHC.HsToCore.Expr ( dsLExpr, dsSyntaxExpr )
=====================================
compiler/GHC/Parser/Errors/Types.hs
=====================================
@@ -6,7 +6,6 @@ module GHC.Parser.Errors.Types where
import GHC.Prelude
-import GHC.Core.TyCon (Role)
import GHC.Data.FastString
import GHC.Hs
import GHC.Parser.Types
=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -134,7 +134,7 @@ import GHC.Hs -- Lots of it
import GHC.Core.TyCon ( TyCon, isTupleTyCon, tyConSingleDataCon_maybe )
import GHC.Core.DataCon ( DataCon, dataConTyCon, dataConName )
import GHC.Core.ConLike ( ConLike(..) )
-import GHC.Core.Coercion.Axiom ( Role, fsFromRole )
+import GHC.Core.Coercion.Axiom ( fsFromRole )
import GHC.Types.Name.Reader
import GHC.Types.Name
import GHC.Types.Basic
@@ -170,8 +170,6 @@ import GHC.Unit.Module.Warnings
import GHC.Utils.Panic
import qualified GHC.Data.Strict as Strict
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad
import Text.ParserCombinators.ReadP as ReadP
import Data.Char
=====================================
compiler/GHC/Rename/Bind.hs
=====================================
@@ -77,8 +77,6 @@ import GHC.Utils.Panic
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad
import Data.List ( partition )
import Data.List.NonEmpty ( NonEmpty(..) )
=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -62,8 +62,6 @@ module GHC.Rename.Env (
import GHC.Prelude
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import GHC.Iface.Load
import GHC.Iface.Env
import GHC.Hs
=====================================
compiler/GHC/Rename/Expr.hs
=====================================
@@ -75,8 +75,6 @@ import GHC.Data.Maybe
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad
import qualified Data.Foldable as Partial (maximum)
import Data.List (unzip4)
=====================================
compiler/GHC/Rename/HsType.hs
=====================================
@@ -74,16 +74,13 @@ import GHC.Types.FieldLabel
import GHC.Types.Error
import GHC.Utils.Misc
-import GHC.Types.Fixity ( compareFixity, negateFixity
- , Fixity(..), FixityDirection(..), LexicalFixity(..) )
+import GHC.Types.Fixity ( compareFixity, negateFixity )
import GHC.Types.Basic ( TypeOrKind(..) )
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Data.Maybe
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Data.List (nubBy, partition)
import Control.Monad
=====================================
compiler/GHC/Rename/Pat.hs
=====================================
@@ -65,7 +65,6 @@ import GHC.Rename.HsType
import GHC.Builtin.Names
import GHC.Types.Hint
-import GHC.Types.Fixity (LexicalFixity(..))
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Types.Name.Reader
=====================================
compiler/GHC/Rename/Utils.hs
=====================================
@@ -53,7 +53,6 @@ import GHC.Tc.Utils.Monad
import GHC.Types.Name
import GHC.Types.Name.Set
import GHC.Types.Name.Env
-import GHC.Core.DataCon
import GHC.Types.SrcLoc as SrcLoc
import GHC.Types.SourceFile
import GHC.Types.SourceText ( SourceText(..), IntegralLit )
=====================================
compiler/GHC/Tc/Deriv/Generate.hs
=====================================
@@ -91,8 +91,6 @@ import GHC.Data.Bag
import GHC.Data.Maybe ( expectJust )
import GHC.Unit.Module
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Data.List ( find, partition, intersperse )
-- | A declarative description of an auxiliary binding that should be
=====================================
compiler/GHC/Tc/Deriv/Generics.hs
=====================================
@@ -44,7 +44,6 @@ import GHC.Iface.Env ( newGlobalBinder )
import GHC.Types.Name hiding ( varName )
import GHC.Types.Name.Reader
-import GHC.Types.Fixity
import GHC.Types.Basic
import GHC.Types.SrcLoc
import GHC.Types.Var.Env
@@ -62,8 +61,6 @@ import GHC.Utils.Misc
import GHC.Driver.DynFlags
import GHC.Data.FastString
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad (mplus)
import Data.List (zip4, partition)
import Data.List.NonEmpty (NonEmpty (..), last, nonEmpty)
=====================================
compiler/GHC/Tc/Errors/Ppr.hs
=====================================
@@ -129,8 +129,6 @@ import qualified GHC.LanguageExtensions as LangExt
import GHC.Data.BooleanFormula (pprBooleanFormulaNice)
-import Language.Haskell.Syntax.Basic (field_label, FieldLabelString (..))
-
import Control.Monad (guard)
import qualified Data.Semigroup as S
import Data.List.NonEmpty (NonEmpty(..))
=====================================
compiler/GHC/Tc/Errors/Types.hs
=====================================
@@ -234,7 +234,7 @@ import GHC.Core.FamInstEnv (FamInst)
import GHC.Core.InstEnv (LookupInstanceErrReason, ClsInst, DFunId)
import GHC.Core.PatSyn (PatSyn)
import GHC.Core.Predicate (EqRel, predTypeEqRel)
-import GHC.Core.TyCon (TyCon, Role, FamTyConFlav, AlgTyConRhs)
+import GHC.Core.TyCon (TyCon, FamTyConFlav, AlgTyConRhs)
import GHC.Core.Type (Kind, Type, ThetaType, PredType, ErrorMsgType, ForAllTyFlag, ForAllTyBinder)
import GHC.Driver.Backend (Backend)
@@ -248,8 +248,6 @@ import GHC.Data.FastString (FastString)
import GHC.Data.Pair
import GHC.Exception.Type (SomeException)
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import Data.Typeable (Typeable)
=====================================
compiler/GHC/Tc/Gen/App.hs
=====================================
@@ -65,7 +65,6 @@ import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic( isBoxed )
import Control.Monad
import Data.Function
=====================================
compiler/GHC/Tc/Gen/Expr.hs
=====================================
@@ -27,8 +27,6 @@ module GHC.Tc.Gen.Expr
import GHC.Prelude
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import {-# SOURCE #-} GHC.Tc.Gen.Splice
( tcTypedSplice, tcTypedBracket, tcUntypedBracket, getUntypedSpliceBody )
=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -59,7 +59,6 @@ import GHC.Core.DataCon
import GHC.Core.PatSyn
import GHC.Core.ConLike
import GHC.Builtin.Names
-import GHC.Types.Basic hiding (SuccessFlag(..))
import GHC.Driver.DynFlags
import GHC.Types.SrcLoc
import GHC.Types.Var.Set
@@ -73,7 +72,6 @@ import GHC.Data.FastString
import qualified Data.List.NonEmpty as NE
import GHC.Data.List.SetOps ( getNth )
-import Language.Haskell.Syntax.Basic (FieldLabelString(..), LexicalFixity(..))
import Data.List( partition )
import Control.Monad.Trans.Writer.CPS
=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -105,8 +105,6 @@ import GHC.Utils.Panic
import GHC.Utils.Constants (debugIsOn)
import GHC.Utils.Misc
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad
import Data.Foldable ( toList, traverse_ )
import Data.Functor.Identity
=====================================
compiler/GHC/Tc/TyCl/Instance.hs
=====================================
@@ -72,7 +72,6 @@ import GHC.Types.Var as Var
import GHC.Types.Var.Env
import GHC.Types.Var.Set
import GHC.Types.Basic
-import GHC.Types.Fixity
import GHC.Types.Id
import GHC.Types.SourceFile
import GHC.Types.SourceText
=====================================
compiler/GHC/Tc/TyCl/Utils.hs
=====================================
@@ -77,8 +77,6 @@ import GHC.Types.Unique.Set
import GHC.Types.TyThing
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad
{-
=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -85,8 +85,6 @@ import GHC.Utils.Misc( HasDebugCallStack, nTimes )
import GHC.Types.Unique
import GHC.Types.Unique.Supply
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import qualified Data.Kind as Hs
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe (isNothing)
=====================================
compiler/GHC/Tc/Validity.hs
=====================================
@@ -81,8 +81,6 @@ import GHC.Utils.Panic
import GHC.Data.List.SetOps
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad
import Data.Foldable
import Data.Function
=====================================
compiler/GHC/ThToHs.hs
=====================================
@@ -40,7 +40,6 @@ import qualified GHC.Core.Coercion as Coercion ( Role(..) )
import GHC.Builtin.Types
import GHC.Builtin.Types.Prim( fUNTyCon )
import GHC.Types.Basic as Hs
-import GHC.Types.Fixity as Hs
import GHC.Types.ForeignCall
import GHC.Types.Unique
import GHC.Types.SourceText
@@ -53,8 +52,6 @@ import GHC.Data.EnumSet (EnumSet)
import qualified GHC.Data.EnumSet as EnumSet
import qualified GHC.LanguageExtensions as LangExt
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import qualified Data.ByteString as BS
import Control.Monad( unless )
import Data.Bifunctor (first)
=====================================
utils/check-exact/ExactPrint.hs
=====================================
@@ -35,13 +35,11 @@ module ExactPrint
import GHC
import GHC.Base (NonEmpty(..))
-import GHC.Core.Coercion.Axiom (Role(..))
import qualified GHC.Data.BooleanFormula as BF
import GHC.Data.FastString
import qualified GHC.Data.Strict as Strict
import GHC.TypeLits
import GHC.Types.Basic hiding (EP)
-import GHC.Types.Fixity
import GHC.Types.ForeignCall
import GHC.Types.Name.Reader
import GHC.Types.PkgQual
@@ -53,8 +51,6 @@ import GHC.Utils.Misc
import GHC.Utils.Outputable hiding ( (<>) )
import GHC.Utils.Panic
-import Language.Haskell.Syntax.Basic (FieldLabelString(..))
-
import Control.Monad (forM, when, unless)
import Control.Monad.Identity (Identity(..))
import qualified Control.Monad.Reader as Reader
=====================================
utils/haddock/haddock-api/src/Haddock/Convert.hs
=====================================
@@ -60,7 +60,6 @@ import GHC.Core.TyCon
import GHC.Core.Type
import GHC.Hs
import GHC.Types.Basic (DefMethSpec (..), TopLevelFlag (..), TupleSort (..))
-import GHC.Types.Fixity (LexicalFixity (..))
import GHC.Types.Id (idType, setIdType)
import GHC.Types.Name
import GHC.Types.Name.Reader (mkVarUnqual)
@@ -80,7 +79,6 @@ import GHC.Utils.Misc
, filterOut
)
import GHC.Utils.Panic.Plain (assert)
-import Language.Haskell.Syntax.Basic (FieldLabelString (..))
import Haddock.GhcUtils (defaultRuntimeRepVars, mkEmptySigType, orderedFVs)
import Haddock.Interface.RenameType
=====================================
utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs
=====================================
@@ -37,7 +37,7 @@ import GHC hiding (NoLink, HsTypeGhcPsExt (..))
import GHC.Builtin.Types (eqTyCon_RDR, tupleDataConName, tupleTyConName)
import GHC.Core.TyCon (tyConResKind)
import GHC.Driver.DynFlags (getDynFlags)
-import GHC.Types.Basic (Boxity (..), TopLevelFlag (..), TupleSort (..))
+import GHC.Types.Basic (TopLevelFlag (..), TupleSort (..))
import GHC.Types.Name
import GHC.Types.Name.Reader (RdrName (Exact))
import Language.Haskell.Syntax.BooleanFormula(BooleanFormula(..))
=====================================
utils/haddock/haddock-api/src/Haddock/Types.hs
=====================================
@@ -56,7 +56,6 @@ import GHC.Data.BooleanFormula (BooleanFormula)
import GHC.Driver.Session (Language)
import qualified GHC.LanguageExtensions as LangExt
import GHC.Core.InstEnv (is_dfun_name)
-import GHC.Types.Fixity (Fixity (..))
import GHC.Types.Name (stableNameCmp)
import GHC.Types.Name.Occurrence
import GHC.Types.Name.Reader (RdrName (..))
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/544b9ec9e34f21eb49d2a53c07b03ff…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/544b9ec9e34f21eb49d2a53c07b03ff…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][master] Skip uniques test if sources are not available
by Marge Bot (@marge-bot) 27 Oct '25
by Marge Bot (@marge-bot) 27 Oct '25
27 Oct '25
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
5dc2e9ea by Julian Ospald at 2025-10-27T18:17:23-04:00
Skip uniques test if sources are not available
- - - - -
1 changed file:
- testsuite/tests/linters/all.T
Changes:
=====================================
testsuite/tests/linters/all.T
=====================================
@@ -3,7 +3,7 @@ def normalise_nos(s):
setTestOpts(no_deps) # linters don't need GHC to be built
-test('uniques', [extra_files(["checkUniques"])], makefile_test, ['uniques'])
+test('uniques', [extra_files(["checkUniques"]), unless(in_tree_compiler(), skip)], makefile_test, ['uniques'])
test('makefiles', [ req_ls_files
, extra_files(["regex-linters"]) ]
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dc2e9eaf60fd72771bf2e8112aec18…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dc2e9eaf60fd72771bf2e8112aec18…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/occ_anal_tuning] 2 commits: Add a perf test for #26425
by Andreas Klebinger (@AndreasK) 27 Oct '25
by Andreas Klebinger (@AndreasK) 27 Oct '25
27 Oct '25
Andreas Klebinger pushed to branch wip/andreask/occ_anal_tuning at Glasgow Haskell Compiler / GHC
Commits:
500cae5a by Andreas Klebinger at 2025-10-27T18:56:35+01:00
Add a perf test for #26425
- - - - -
17a3c5a1 by Andreas Klebinger at 2025-10-27T18:56:42+01:00
OccAnal: Be stricter.
* When combining usageDetails.
* When constructing core expressions.
In combineUsageDetails when combining the underlying adds we compute a
new `LocalOcc` for each entry by combining the two existing ones.
Rather than wait for those entries to be forced down the road we now
force them immediately. Speeding up T26425 by about 10% with little
effect on the common case.
We also force binders we put into the Core AST everywhere now.
Failure to do so risks leaking the occ env used to set the binders
OccInfo.
For T26425 compiler residency went down by a factor of ~10x.
Compile time also improved by a factor of ~1.6.
-------------------------
Metric Decrease:
T26425
-------------------------
- - - - -
5 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
Changes:
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -9,6 +9,8 @@
-- many /other/ arguments the function has. Inconsistent unboxing is very
-- bad for performance, so I increased the limit to allow it to unbox
-- consistently.
+-- AK: Seems we no longer unbox OccEnv now anyway so it might be redundant.
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -967,6 +969,11 @@ occAnalBind
-> ([CoreBind] -> r -> r) -- How to combine the scope with new binds
-> WithUsageDetails r -- Of the whole let(rec)
+-- While not allocating any less inlining occAnalBind turns calls to the passed functions
+-- into known calls. One might assume this doesn't matter, but for let heavy
+-- code I observed speed ups as big as 10-20%!
+{-# INLINE occAnalBind #-}
+
occAnalBind env lvl ire (Rec pairs) thing_inside combine
= addInScopeList env (map fst pairs) $ \env ->
let WUD body_uds body' = thing_inside env
@@ -984,7 +991,7 @@ occAnalBind !env lvl ire (NonRec bndr rhs) thing_inside combine
= -- Analyse the RHS and /then/ the body
let -- Analyse the rhs first, generating rhs_uds
!(rhs_uds_s, bndr', rhs') = occAnalNonRecRhs env lvl ire mb_join bndr rhs
- rhs_uds = foldr1 orUDs rhs_uds_s -- NB: orUDs. See (W4) of
+ rhs_uds = foldl1' orUDs rhs_uds_s -- NB: orUDs. See (W4) of
-- Note [Occurrence analysis for join points]
-- Now analyse the body, adding the join point
@@ -1049,6 +1056,7 @@ occAnalNonRecRhs !env lvl imp_rule_edges mb_join bndr rhs
-- Match join arity O from mb_join_arity with manifest join arity M as
-- returned by of occAnalLamTail. It's totally OK for them to mismatch;
-- hence adjust the UDs from the RHS
+
WUD adj_rhs_uds final_rhs = adjustNonRecRhs mb_join $
occAnalLamTail rhs_env rhs
final_bndr_with_rules
@@ -2188,7 +2196,8 @@ occ_anal_lam_tail env expr@(Lam {})
go env rev_bndrs body
= addInScope env rev_bndrs $ \env ->
let !(WUD usage body') = occ_anal_lam_tail env body
- wrap_lam body bndr = Lam (tagLamBinder usage bndr) body
+ wrap_lam !body !bndr = let !bndr' = tagLamBinder usage bndr
+ in Lam bndr' body
in WUD (usage `addLamCoVarOccs` rev_bndrs)
(foldl' wrap_lam body' rev_bndrs)
@@ -2541,7 +2550,7 @@ occAnal env (Case scrut bndr ty alts)
let alt_env = addBndrSwap scrut' bndr $
setTailCtxt env -- Kill off OccRhs
WUD alts_usage alts' = do_alts alt_env alts
- tagged_bndr = tagLamBinder alts_usage bndr
+ !tagged_bndr = tagLamBinder alts_usage bndr
in WUD alts_usage (tagged_bndr, alts')
total_usage = markAllNonTail scrut_usage `andUDs` alts_usage
@@ -2559,11 +2568,12 @@ occAnal env (Case scrut bndr ty alts)
do_alt !env (Alt con bndrs rhs)
= addInScopeList env bndrs $ \ env ->
let WUD rhs_usage rhs' = occAnal env rhs
- tagged_bndrs = tagLamBinders rhs_usage bndrs
+ !tagged_bndrs = tagLamBinders rhs_usage bndrs
in -- See Note [Binders in case alternatives]
WUD rhs_usage (Alt con tagged_bndrs rhs')
occAnal env (Let bind body)
+ -- TODO: Would be nice to use a strict version of mkLets here
= occAnalBind env NotTopLevel noImpRuleEdges bind
(\env -> occAnal env body) mkLets
@@ -2644,10 +2654,12 @@ occAnalApp !env (Var fun, args, ticks)
| fun `hasKey` runRWKey
, [t1, t2, arg] <- args
, WUD usage arg' <- adjustNonRecRhs (JoinPoint 1) $ occAnalLamTail env arg
- = WUD usage (mkTicks ticks $ mkApps (Var fun) [t1, t2, arg'])
+ = let app_out = (mkTicks ticks $ mkApps (Var fun) [t1, t2, arg'])
+ in WUD usage app_out
occAnalApp env (Var fun_id, args, ticks)
- = WUD all_uds (mkTicks ticks app')
+ = let app_out = (mkTicks ticks app')
+ in WUD all_uds app_out
where
-- Lots of banged bindings: this is a very heavily bit of code,
-- so it pays not to make lots of thunks here, all of which
@@ -2692,8 +2704,9 @@ occAnalApp env (Var fun_id, args, ticks)
-- See Note [Sources of one-shot information], bullet point A']
occAnalApp env (fun, args, ticks)
- = WUD (markAllNonTail (fun_uds `andUDs` args_uds))
- (mkTicks ticks app')
+ = let app_out = (mkTicks ticks app')
+ in WUD (markAllNonTail (fun_uds `andUDs` args_uds)) app_out
+
where
!(WUD args_uds app') = occAnalArgs env fun' args []
!(WUD fun_uds fun') = occAnal (addAppCtxt env args) fun
@@ -3650,8 +3663,8 @@ data WithTailUsageDetails a = WTUD !TailUsageDetails !a
-------------------
-- UsageDetails API
-andUDs, orUDs
- :: UsageDetails -> UsageDetails -> UsageDetails
+andUDs:: UsageDetails -> UsageDetails -> UsageDetails
+orUDs :: UsageDetails -> UsageDetails -> UsageDetails
andUDs = combineUsageDetailsWith andLocalOcc
orUDs = combineUsageDetailsWith orLocalOcc
@@ -3766,10 +3779,12 @@ combineUsageDetailsWith plus_occ_info
| isEmptyVarEnv env1 = uds2
| isEmptyVarEnv env2 = uds1
| otherwise
- = UD { ud_env = plusVarEnv_C plus_occ_info env1 env2
- , ud_z_many = plusVarEnv z_many1 z_many2
+ -- Using strictPlusVarEnv here speeds up the test T26425 by about 10% by avoiding
+ -- intermediate thunks.
+ = UD { ud_env = strictPlusVarEnv_C plus_occ_info env1 env2
+ , ud_z_many = strictPlusVarEnv z_many1 z_many2
, ud_z_in_lam = plusVarEnv z_in_lam1 z_in_lam2
- , ud_z_tail = plusVarEnv z_tail1 z_tail2 }
+ , ud_z_tail = strictPlusVarEnv z_tail1 z_tail2 }
lookupLetOccInfo :: UsageDetails -> Id -> OccInfo
-- Don't use locally-generated occ_info for exported (visible-elsewhere)
@@ -3847,7 +3862,7 @@ tagLamBinders :: UsageDetails -- Of scope
-> [Id] -- Binders
-> [IdWithOccInfo] -- Tagged binders
tagLamBinders usage binders
- = map (tagLamBinder usage) binders
+ = strictMap (tagLamBinder usage) binders
tagLamBinder :: UsageDetails -- Of scope
-> Id -- Binder
=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -51,7 +51,9 @@ module GHC.Types.Unique.FM (
delListFromUFM,
delListFromUFM_Directly,
plusUFM,
+ strictPlusUFM,
plusUFM_C,
+ strictPlusUFM_C,
plusUFM_CD,
plusUFM_CD2,
mergeUFM,
@@ -261,16 +263,24 @@ delListFromUFM_Directly = foldl' delFromUFM_Directly
delFromUFM_Directly :: UniqFM key elt -> Unique -> UniqFM key elt
delFromUFM_Directly (UFM m) u = UFM (M.delete (getKey u) m)
--- Bindings in right argument shadow those in the left
+-- | Bindings in right argument shadow those in the left.
+--
+-- Unlike containers this union is right-biased for historic reasons.
plusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt
--- M.union is left-biased, plusUFM should be right-biased.
plusUFM (UFM x) (UFM y) = UFM (M.union y x)
-- Note (M.union y x), with arguments flipped
-- M.union is left-biased, plusUFM should be right-biased.
+-- | Right biased
+strictPlusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM (UFM x) (UFM y) = UFM (MS.union y x)
+
plusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y)
+strictPlusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM_C f (UFM x) (UFM y) = UFM (MS.unionWith f x y)
+
-- | `plusUFM_CD f m1 d1 m2 d2` merges the maps using `f` as the
-- combinding function and `d1` resp. `d2` as the default value if
-- there is no entry in `m1` reps. `m2`. The domain is the union of
=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -12,7 +12,8 @@ module GHC.Types.Var.Env (
elemVarEnv, disjointVarEnv, anyVarEnv,
extendVarEnv, extendVarEnv_C, extendVarEnv_Acc,
extendVarEnvList,
- plusVarEnv, plusVarEnv_C, plusVarEnv_CD, plusMaybeVarEnv_C,
+ strictPlusVarEnv, plusVarEnv, plusVarEnv_C, strictPlusVarEnv_C,
+ plusVarEnv_CD, plusMaybeVarEnv_C,
plusVarEnvList, alterVarEnv,
delVarEnvList, delVarEnv,
minusVarEnv,
@@ -511,6 +512,7 @@ extendVarEnv :: VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_C :: (a->a->a) -> VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_Acc :: (a->b->b) -> (a->b) -> VarEnv b -> Var -> a -> VarEnv b
plusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
plusVarEnvList :: [VarEnv a] -> VarEnv a
extendVarEnvList :: VarEnv a -> [(Var, a)] -> VarEnv a
varEnvDomain :: VarEnv elt -> UnVarSet
@@ -522,6 +524,7 @@ delVarEnvList :: Foldable f => VarEnv a -> f Var -> VarEnv a
delVarEnv :: VarEnv a -> Var -> VarEnv a
minusVarEnv :: VarEnv a -> VarEnv b -> VarEnv a
plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
plusVarEnv_CD :: (a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a
plusMaybeVarEnv_C :: (a -> a -> Maybe a) -> VarEnv a -> VarEnv a -> VarEnv a
mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b
@@ -548,6 +551,7 @@ extendVarEnv_C = addToUFM_C
extendVarEnv_Acc = addToUFM_Acc
extendVarEnvList = addListToUFM
plusVarEnv_C = plusUFM_C
+strictPlusVarEnv_C = strictPlusUFM_C
plusVarEnv_CD = plusUFM_CD
plusMaybeVarEnv_C = plusMaybeUFM_C
delVarEnvList = delListFromUFM
@@ -556,6 +560,7 @@ delVarEnvList = delListFromUFM
delVarEnv = delFromUFM
minusVarEnv = minusUFM
plusVarEnv = plusUFM
+strictPlusVarEnv = strictPlusUFM
plusVarEnvList = plusUFMList
-- lookupVarEnv is very hot (in part due to being called by substTyVar),
-- if it's not inlined than the mere allocation of the Just constructor causes
=====================================
testsuite/tests/perf/compiler/T26425.hs
=====================================
@@ -0,0 +1,514 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Reproducer (strToInt) where
+
+import qualified Data.Text as T
+
+{- This program results in a nested chain of join points and cases which tests
+ primarily OccAnal and Unfolding performance.
+-}
+
+strToInt :: T.Text -> Maybe Int
+strToInt txt = case txt of
+ "0" -> Just 0
+ "1" -> Just 1
+ "2" -> Just 2
+ "3" -> Just 3
+ "4" -> Just 4
+ "5" -> Just 5
+ "6" -> Just 6
+ "7" -> Just 7
+ "8" -> Just 8
+ "9" -> Just 9
+ "10" -> Just 10
+ "11" -> Just 11
+ "12" -> Just 12
+ "13" -> Just 13
+ "14" -> Just 14
+ "15" -> Just 15
+ "16" -> Just 16
+ "17" -> Just 17
+ "18" -> Just 18
+ "19" -> Just 19
+ "20" -> Just 20
+ "21" -> Just 21
+ "22" -> Just 22
+ "23" -> Just 23
+ "24" -> Just 24
+ "25" -> Just 25
+ "26" -> Just 26
+ "27" -> Just 27
+ "28" -> Just 28
+ "29" -> Just 29
+ "30" -> Just 30
+ "31" -> Just 31
+ "32" -> Just 32
+ "33" -> Just 33
+ "34" -> Just 34
+ "35" -> Just 35
+ "36" -> Just 36
+ "37" -> Just 37
+ "38" -> Just 38
+ "39" -> Just 39
+ "40" -> Just 40
+ "41" -> Just 41
+ "42" -> Just 42
+ "43" -> Just 43
+ "44" -> Just 44
+ "45" -> Just 45
+ "46" -> Just 46
+ "47" -> Just 47
+ "48" -> Just 48
+ "49" -> Just 49
+ "50" -> Just 50
+ "51" -> Just 51
+ "52" -> Just 52
+ "53" -> Just 53
+ "54" -> Just 54
+ "55" -> Just 55
+ "56" -> Just 56
+ "57" -> Just 57
+ "58" -> Just 58
+ "59" -> Just 59
+ "60" -> Just 60
+ "61" -> Just 61
+ "62" -> Just 62
+ "63" -> Just 63
+ "64" -> Just 64
+ "65" -> Just 65
+ "66" -> Just 66
+ "67" -> Just 67
+ "68" -> Just 68
+ "69" -> Just 69
+ "70" -> Just 70
+ "71" -> Just 71
+ "72" -> Just 72
+ "73" -> Just 73
+ "74" -> Just 74
+ "75" -> Just 75
+ "76" -> Just 76
+ "77" -> Just 77
+ "78" -> Just 78
+ "79" -> Just 79
+ "80" -> Just 80
+ "81" -> Just 81
+ "82" -> Just 82
+ "83" -> Just 83
+ "84" -> Just 84
+ "85" -> Just 85
+ "86" -> Just 86
+ "87" -> Just 87
+ "88" -> Just 88
+ "89" -> Just 89
+ "90" -> Just 90
+ "91" -> Just 91
+ "92" -> Just 92
+ "93" -> Just 93
+ "94" -> Just 94
+ "95" -> Just 95
+ "96" -> Just 96
+ "97" -> Just 97
+ "98" -> Just 98
+ "99" -> Just 99
+ "100" -> Just 100
+ "101" -> Just 101
+ "102" -> Just 102
+ "103" -> Just 103
+ "104" -> Just 104
+ "105" -> Just 105
+ "106" -> Just 106
+ "107" -> Just 107
+ "108" -> Just 108
+ "109" -> Just 109
+ "110" -> Just 110
+ "111" -> Just 111
+ "112" -> Just 112
+ "113" -> Just 113
+ "114" -> Just 114
+ "115" -> Just 115
+ "116" -> Just 116
+ "117" -> Just 117
+ "118" -> Just 118
+ "119" -> Just 119
+ "120" -> Just 120
+ "121" -> Just 121
+ "122" -> Just 122
+ "123" -> Just 123
+ "124" -> Just 124
+ "125" -> Just 125
+ "126" -> Just 126
+ "127" -> Just 127
+ "128" -> Just 128
+ "129" -> Just 129
+ "130" -> Just 130
+ "131" -> Just 131
+ "132" -> Just 132
+ "133" -> Just 133
+ "134" -> Just 134
+ "135" -> Just 135
+ "136" -> Just 136
+ "137" -> Just 137
+ "138" -> Just 138
+ "139" -> Just 139
+ "140" -> Just 140
+ "141" -> Just 141
+ "142" -> Just 142
+ "143" -> Just 143
+ "144" -> Just 144
+ "145" -> Just 145
+ "146" -> Just 146
+ "147" -> Just 147
+ "148" -> Just 148
+ "149" -> Just 149
+ "150" -> Just 150
+ "151" -> Just 151
+ "152" -> Just 152
+ "153" -> Just 153
+ "154" -> Just 154
+ "155" -> Just 155
+ "156" -> Just 156
+ "157" -> Just 157
+ "158" -> Just 158
+ "159" -> Just 159
+ "160" -> Just 160
+ "161" -> Just 161
+ "162" -> Just 162
+ "163" -> Just 163
+ "164" -> Just 164
+ "165" -> Just 165
+ "166" -> Just 166
+ "167" -> Just 167
+ "168" -> Just 168
+ "169" -> Just 169
+ "170" -> Just 170
+ "171" -> Just 171
+ "172" -> Just 172
+ "173" -> Just 173
+ "174" -> Just 174
+ "175" -> Just 175
+ "176" -> Just 176
+ "177" -> Just 177
+ "178" -> Just 178
+ "179" -> Just 179
+ "180" -> Just 180
+ "181" -> Just 181
+ "182" -> Just 182
+ "183" -> Just 183
+ "184" -> Just 184
+ "185" -> Just 185
+ "186" -> Just 186
+ "187" -> Just 187
+ "188" -> Just 188
+ "189" -> Just 189
+ "190" -> Just 190
+ "191" -> Just 191
+ "192" -> Just 192
+ "193" -> Just 193
+ "194" -> Just 194
+ "195" -> Just 195
+ "196" -> Just 196
+ "197" -> Just 197
+ "198" -> Just 198
+ "199" -> Just 199
+ "200" -> Just 200
+ "201" -> Just 201
+ "202" -> Just 202
+ "203" -> Just 203
+ "204" -> Just 204
+ "205" -> Just 205
+ "206" -> Just 206
+ "207" -> Just 207
+ "208" -> Just 208
+ "209" -> Just 209
+ "210" -> Just 210
+ "211" -> Just 211
+ "212" -> Just 212
+ "213" -> Just 213
+ "214" -> Just 214
+ "215" -> Just 215
+ "216" -> Just 216
+ "217" -> Just 217
+ "218" -> Just 218
+ "219" -> Just 219
+ "220" -> Just 220
+ "221" -> Just 221
+ "222" -> Just 222
+ "223" -> Just 223
+ "224" -> Just 224
+ "225" -> Just 225
+ "226" -> Just 226
+ "227" -> Just 227
+ "228" -> Just 228
+ "229" -> Just 229
+ "230" -> Just 230
+ "231" -> Just 231
+ "232" -> Just 232
+ "233" -> Just 233
+ "234" -> Just 234
+ "235" -> Just 235
+ "236" -> Just 236
+ "237" -> Just 237
+ "238" -> Just 238
+ "239" -> Just 239
+ "240" -> Just 240
+ "241" -> Just 241
+ "242" -> Just 242
+ "243" -> Just 243
+ "244" -> Just 244
+ "245" -> Just 245
+ "246" -> Just 246
+ "247" -> Just 247
+ "248" -> Just 248
+ "249" -> Just 249
+ "250" -> Just 250
+ "251" -> Just 251
+ "252" -> Just 252
+ "253" -> Just 253
+ "254" -> Just 254
+ "255" -> Just 255
+ "256" -> Just 256
+ "257" -> Just 257
+ "258" -> Just 258
+ "259" -> Just 259
+ "260" -> Just 260
+ "261" -> Just 261
+ "262" -> Just 262
+ "263" -> Just 263
+ "264" -> Just 264
+ "265" -> Just 265
+ "266" -> Just 266
+ "267" -> Just 267
+ "268" -> Just 268
+ "269" -> Just 269
+ "270" -> Just 270
+ "271" -> Just 271
+ "272" -> Just 272
+ "273" -> Just 273
+ "274" -> Just 274
+ "275" -> Just 275
+ "276" -> Just 276
+ "277" -> Just 277
+ "278" -> Just 278
+ "279" -> Just 279
+ "280" -> Just 280
+ "281" -> Just 281
+ "282" -> Just 282
+ "283" -> Just 283
+ "284" -> Just 284
+ "285" -> Just 285
+ "286" -> Just 286
+ "287" -> Just 287
+ "288" -> Just 288
+ "289" -> Just 289
+ "290" -> Just 290
+ "291" -> Just 291
+ "292" -> Just 292
+ "293" -> Just 293
+ "294" -> Just 294
+ "295" -> Just 295
+ "296" -> Just 296
+ "297" -> Just 297
+ "298" -> Just 298
+ "299" -> Just 299
+ "300" -> Just 300
+ "301" -> Just 301
+ "302" -> Just 302
+ "303" -> Just 303
+ "304" -> Just 304
+ "305" -> Just 305
+ "306" -> Just 306
+ "307" -> Just 307
+ "308" -> Just 308
+ "309" -> Just 309
+ "310" -> Just 310
+ "311" -> Just 311
+ "312" -> Just 312
+ "313" -> Just 313
+ "314" -> Just 314
+ "315" -> Just 315
+ "316" -> Just 316
+ "317" -> Just 317
+ "318" -> Just 318
+ "319" -> Just 319
+ "320" -> Just 320
+ "321" -> Just 321
+ "322" -> Just 322
+ "323" -> Just 323
+ "324" -> Just 324
+ "325" -> Just 325
+ "326" -> Just 326
+ "327" -> Just 327
+ "328" -> Just 328
+ "329" -> Just 329
+ "330" -> Just 330
+ "331" -> Just 331
+ "332" -> Just 332
+ "333" -> Just 333
+ "334" -> Just 334
+ "335" -> Just 335
+ "336" -> Just 336
+ "337" -> Just 337
+ "338" -> Just 338
+ "339" -> Just 339
+ "340" -> Just 340
+ "341" -> Just 341
+ "342" -> Just 342
+ "343" -> Just 343
+ "344" -> Just 344
+ "345" -> Just 345
+ "346" -> Just 346
+ "347" -> Just 347
+ "348" -> Just 348
+ "349" -> Just 349
+ "350" -> Just 350
+ "351" -> Just 351
+ "352" -> Just 352
+ "353" -> Just 353
+ "354" -> Just 354
+ "355" -> Just 355
+ "356" -> Just 356
+ "357" -> Just 357
+ "358" -> Just 358
+ "359" -> Just 359
+ "360" -> Just 360
+ "361" -> Just 361
+ "362" -> Just 362
+ "363" -> Just 363
+ "364" -> Just 364
+ "365" -> Just 365
+ "366" -> Just 366
+ "367" -> Just 367
+ "368" -> Just 368
+ "369" -> Just 369
+ "370" -> Just 370
+ "371" -> Just 371
+ "372" -> Just 372
+ "373" -> Just 373
+ "374" -> Just 374
+ "375" -> Just 375
+ "376" -> Just 376
+ "377" -> Just 377
+ "378" -> Just 378
+ "379" -> Just 379
+ "380" -> Just 380
+ "381" -> Just 381
+ "382" -> Just 382
+ "383" -> Just 383
+ "384" -> Just 384
+ "385" -> Just 385
+ "386" -> Just 386
+ "387" -> Just 387
+ "388" -> Just 388
+ "389" -> Just 389
+ "390" -> Just 390
+ "391" -> Just 391
+ "392" -> Just 392
+ "393" -> Just 393
+ "394" -> Just 394
+ "395" -> Just 395
+ "396" -> Just 396
+ "397" -> Just 397
+ "398" -> Just 398
+ "399" -> Just 399
+ "400" -> Just 400
+ "401" -> Just 401
+ "402" -> Just 402
+ "403" -> Just 403
+ "404" -> Just 404
+ "405" -> Just 405
+ "406" -> Just 406
+ "407" -> Just 407
+ "408" -> Just 408
+ "409" -> Just 409
+ "410" -> Just 410
+ "411" -> Just 411
+ "412" -> Just 412
+ "413" -> Just 413
+ "414" -> Just 414
+ "415" -> Just 415
+ "416" -> Just 416
+ "417" -> Just 417
+ "418" -> Just 418
+ "419" -> Just 419
+ "420" -> Just 420
+ "421" -> Just 421
+ "422" -> Just 422
+ "423" -> Just 423
+ "424" -> Just 424
+ "425" -> Just 425
+ "426" -> Just 426
+ "427" -> Just 427
+ "428" -> Just 428
+ "429" -> Just 429
+ "430" -> Just 430
+ "431" -> Just 431
+ "432" -> Just 432
+ "433" -> Just 433
+ "434" -> Just 434
+ "435" -> Just 435
+ "436" -> Just 436
+ "437" -> Just 437
+ "438" -> Just 438
+ "439" -> Just 439
+ "440" -> Just 440
+ "441" -> Just 441
+ "442" -> Just 442
+ "443" -> Just 443
+ "444" -> Just 444
+ "445" -> Just 445
+ "446" -> Just 446
+ "447" -> Just 447
+ "448" -> Just 448
+ "449" -> Just 449
+ "450" -> Just 450
+ "451" -> Just 451
+ "452" -> Just 452
+ "453" -> Just 453
+ "454" -> Just 454
+ "455" -> Just 455
+ "456" -> Just 456
+ "457" -> Just 457
+ "458" -> Just 458
+ "459" -> Just 459
+ "460" -> Just 460
+ "461" -> Just 461
+ "462" -> Just 462
+ "463" -> Just 463
+ "464" -> Just 464
+ "465" -> Just 465
+ "466" -> Just 466
+ "467" -> Just 467
+ "468" -> Just 468
+ "469" -> Just 469
+ "470" -> Just 470
+ "471" -> Just 471
+ "472" -> Just 472
+ "473" -> Just 473
+ "474" -> Just 474
+ "475" -> Just 475
+ "476" -> Just 476
+ "477" -> Just 477
+ "478" -> Just 478
+ "479" -> Just 479
+ "480" -> Just 480
+ "481" -> Just 481
+ "482" -> Just 482
+ "483" -> Just 483
+ "484" -> Just 484
+ "485" -> Just 485
+ "486" -> Just 486
+ "487" -> Just 487
+ "488" -> Just 488
+ "489" -> Just 489
+ "490" -> Just 490
+ "491" -> Just 491
+ "492" -> Just 492
+ "493" -> Just 493
+ "494" -> Just 494
+ "495" -> Just 495
+ "496" -> Just 496
+ "497" -> Just 497
+ "498" -> Just 498
+ "499" -> Just 499
+ "500" -> Just 500
+ _ -> Nothing
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -806,3 +806,8 @@ test('interpreter_steplocal',
],
ghci_script,
['interpreter_steplocal.script'])
+
+test ('T26425',
+ [ collect_compiler_stats('all',5) ],
+ compile,
+ ['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1434feb89e7336135d313942a5abc0…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1434feb89e7336135d313942a5abc0…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/andreask/occ_anal_tuning] 2 commits: OccAnal: Be stricter.
by Andreas Klebinger (@AndreasK) 27 Oct '25
by Andreas Klebinger (@AndreasK) 27 Oct '25
27 Oct '25
Andreas Klebinger pushed to branch wip/andreask/occ_anal_tuning at Glasgow Haskell Compiler / GHC
Commits:
cb1ea0c9 by Andreas Klebinger at 2025-10-27T18:43:40+01:00
OccAnal: Be stricter.
* When combining usageDetails.
* When constructing core expressions.
In combineUsageDetails when combining the underlying adds we compute a
new `LocalOcc` for each entry by combining the two existing ones.
Rather than wait for those entries to be forced down the road we now
force them immediately. Speeding up T26425 by about 10% with little
effect on the common case.
We also force binders we put into the Core AST everywhere now.
Failure to do so risks leaking the occ env used to set the binders
OccInfo.
For T26425 compiler residency went down by a factor of ~10x.
Compile time also improved by a factor of ~1.6.
-------------------------
Metric Decrease:
T26425
-------------------------
- - - - -
1434feb8 by Andreas Klebinger at 2025-10-27T18:47:18+01:00
Add a perf test for #26425
- - - - -
6 changed files:
- compiler/GHC/Core/Opt/OccurAnal.hs
- compiler/GHC/Data/Graph/UnVar.hs
- compiler/GHC/Types/Unique/FM.hs
- compiler/GHC/Types/Var/Env.hs
- + testsuite/tests/perf/compiler/T26425.hs
- testsuite/tests/perf/compiler/all.T
Changes:
=====================================
compiler/GHC/Core/Opt/OccurAnal.hs
=====================================
@@ -9,6 +9,8 @@
-- many /other/ arguments the function has. Inconsistent unboxing is very
-- bad for performance, so I increased the limit to allow it to unbox
-- consistently.
+-- AK: Seems we no longer unbox OccEnv now anyway so it might be redundant.
+
{-
(c) The GRASP/AQUA Project, Glasgow University, 1992-1998
@@ -967,6 +969,11 @@ occAnalBind
-> ([CoreBind] -> r -> r) -- How to combine the scope with new binds
-> WithUsageDetails r -- Of the whole let(rec)
+-- While not allocating any less inlining occAnalBind turns calls to the passed functions
+-- into known calls. One might assume this doesn't matter, but for let heavy
+-- code I observed speed ups as big as 10-20%!
+{-# INLINE occAnalBind #-}
+
occAnalBind env lvl ire (Rec pairs) thing_inside combine
= addInScopeList env (map fst pairs) $ \env ->
let WUD body_uds body' = thing_inside env
@@ -984,7 +991,7 @@ occAnalBind !env lvl ire (NonRec bndr rhs) thing_inside combine
= -- Analyse the RHS and /then/ the body
let -- Analyse the rhs first, generating rhs_uds
!(rhs_uds_s, bndr', rhs') = occAnalNonRecRhs env lvl ire mb_join bndr rhs
- rhs_uds = foldr1 orUDs rhs_uds_s -- NB: orUDs. See (W4) of
+ rhs_uds = foldl1' orUDs rhs_uds_s -- NB: orUDs. See (W4) of
-- Note [Occurrence analysis for join points]
-- Now analyse the body, adding the join point
@@ -1049,6 +1056,7 @@ occAnalNonRecRhs !env lvl imp_rule_edges mb_join bndr rhs
-- Match join arity O from mb_join_arity with manifest join arity M as
-- returned by of occAnalLamTail. It's totally OK for them to mismatch;
-- hence adjust the UDs from the RHS
+
WUD adj_rhs_uds final_rhs = adjustNonRecRhs mb_join $
occAnalLamTail rhs_env rhs
final_bndr_with_rules
@@ -2188,7 +2196,8 @@ occ_anal_lam_tail env expr@(Lam {})
go env rev_bndrs body
= addInScope env rev_bndrs $ \env ->
let !(WUD usage body') = occ_anal_lam_tail env body
- wrap_lam body bndr = Lam (tagLamBinder usage bndr) body
+ wrap_lam !body !bndr = let !bndr' = tagLamBinder usage bndr
+ in Lam bndr' body
in WUD (usage `addLamCoVarOccs` rev_bndrs)
(foldl' wrap_lam body' rev_bndrs)
@@ -2541,7 +2550,7 @@ occAnal env (Case scrut bndr ty alts)
let alt_env = addBndrSwap scrut' bndr $
setTailCtxt env -- Kill off OccRhs
WUD alts_usage alts' = do_alts alt_env alts
- tagged_bndr = tagLamBinder alts_usage bndr
+ !tagged_bndr = tagLamBinder alts_usage bndr
in WUD alts_usage (tagged_bndr, alts')
total_usage = markAllNonTail scrut_usage `andUDs` alts_usage
@@ -2559,11 +2568,12 @@ occAnal env (Case scrut bndr ty alts)
do_alt !env (Alt con bndrs rhs)
= addInScopeList env bndrs $ \ env ->
let WUD rhs_usage rhs' = occAnal env rhs
- tagged_bndrs = tagLamBinders rhs_usage bndrs
+ !tagged_bndrs = tagLamBinders rhs_usage bndrs
in -- See Note [Binders in case alternatives]
WUD rhs_usage (Alt con tagged_bndrs rhs')
occAnal env (Let bind body)
+ -- TODO: Would be nice to use a strict version of mkLets here
= occAnalBind env NotTopLevel noImpRuleEdges bind
(\env -> occAnal env body) mkLets
@@ -2644,10 +2654,12 @@ occAnalApp !env (Var fun, args, ticks)
| fun `hasKey` runRWKey
, [t1, t2, arg] <- args
, WUD usage arg' <- adjustNonRecRhs (JoinPoint 1) $ occAnalLamTail env arg
- = WUD usage (mkTicks ticks $ mkApps (Var fun) [t1, t2, arg'])
+ = let app_out = (mkTicks ticks $ mkApps (Var fun) [t1, t2, arg'])
+ in WUD usage app_out
occAnalApp env (Var fun_id, args, ticks)
- = WUD all_uds (mkTicks ticks app')
+ = let app_out = (mkTicks ticks app')
+ in WUD all_uds app_out
where
-- Lots of banged bindings: this is a very heavily bit of code,
-- so it pays not to make lots of thunks here, all of which
@@ -2692,8 +2704,9 @@ occAnalApp env (Var fun_id, args, ticks)
-- See Note [Sources of one-shot information], bullet point A']
occAnalApp env (fun, args, ticks)
- = WUD (markAllNonTail (fun_uds `andUDs` args_uds))
- (mkTicks ticks app')
+ = let app_out = (mkTicks ticks app')
+ in WUD (markAllNonTail (fun_uds `andUDs` args_uds)) app_out
+
where
!(WUD args_uds app') = occAnalArgs env fun' args []
!(WUD fun_uds fun') = occAnal (addAppCtxt env args) fun
@@ -3650,8 +3663,8 @@ data WithTailUsageDetails a = WTUD !TailUsageDetails !a
-------------------
-- UsageDetails API
-andUDs, orUDs
- :: UsageDetails -> UsageDetails -> UsageDetails
+andUDs:: UsageDetails -> UsageDetails -> UsageDetails
+orUDs :: UsageDetails -> UsageDetails -> UsageDetails
andUDs = combineUsageDetailsWith andLocalOcc
orUDs = combineUsageDetailsWith orLocalOcc
@@ -3766,10 +3779,12 @@ combineUsageDetailsWith plus_occ_info
| isEmptyVarEnv env1 = uds2
| isEmptyVarEnv env2 = uds1
| otherwise
- = UD { ud_env = plusVarEnv_C plus_occ_info env1 env2
- , ud_z_many = plusVarEnv z_many1 z_many2
+ -- Using strictPlusVarEnv here speeds up the test T26425 by about 10% by avoiding
+ -- intermediate thunks.
+ = UD { ud_env = strictPlusVarEnv_C plus_occ_info env1 env2
+ , ud_z_many = strictPlusVarEnv z_many1 z_many2
, ud_z_in_lam = plusVarEnv z_in_lam1 z_in_lam2
- , ud_z_tail = plusVarEnv z_tail1 z_tail2 }
+ , ud_z_tail = strictPlusVarEnv z_tail1 z_tail2 }
lookupLetOccInfo :: UsageDetails -> Id -> OccInfo
-- Don't use locally-generated occ_info for exported (visible-elsewhere)
@@ -3847,7 +3862,7 @@ tagLamBinders :: UsageDetails -- Of scope
-> [Id] -- Binders
-> [IdWithOccInfo] -- Tagged binders
tagLamBinders usage binders
- = map (tagLamBinder usage) binders
+ = strictMap (tagLamBinder usage) binders
tagLamBinder :: UsageDetails -- Of scope
-> Id -- Binder
=====================================
compiler/GHC/Data/Graph/UnVar.hs
=====================================
@@ -17,8 +17,8 @@ equal to g, but twice as expensive and large.
module GHC.Data.Graph.UnVar
( UnVarSet
, emptyUnVarSet, mkUnVarSet, unionUnVarSet, unionUnVarSets
- , extendUnVarSet, extendUnVarSetList, delUnVarSet, delUnVarSetList
- , elemUnVarSet, isEmptyUnVarSet
+ , extendUnVarSet, extendUnVarSet_Directly, extendUnVarSetList, delUnVarSet, delUnVarSetList
+ , elemUnVarSet, elemUnVarSet_Directly, isEmptyUnVarSet
, UnVarGraph
, emptyUnVarGraph
, unionUnVarGraph, unionUnVarGraphs
@@ -60,6 +60,9 @@ emptyUnVarSet = UnVarSet S.empty
elemUnVarSet :: Var -> UnVarSet -> Bool
elemUnVarSet v (UnVarSet s) = k v `S.member` s
+{-# INLINE elemUnVarSet_Directly #-}
+elemUnVarSet_Directly :: Uniquable key => key -> UnVarSet -> Bool
+elemUnVarSet_Directly v (UnVarSet s) = (getKey $ getUnique v) `S.member` s
isEmptyUnVarSet :: UnVarSet -> Bool
isEmptyUnVarSet (UnVarSet s) = S.null s
@@ -82,6 +85,10 @@ mkUnVarSet vs = UnVarSet $ S.fromList $ map k vs
extendUnVarSet :: Var -> UnVarSet -> UnVarSet
extendUnVarSet v (UnVarSet s) = UnVarSet $ S.insert (k v) s
+{-# INLINE extendUnVarSet_Directly #-}
+extendUnVarSet_Directly :: Uniquable key => key -> UnVarSet -> UnVarSet
+extendUnVarSet_Directly u (UnVarSet s) = UnVarSet $ S.insert (getKey $ getUnique u) s
+
extendUnVarSetList :: [Var] -> UnVarSet -> UnVarSet
extendUnVarSetList vs s = s `unionUnVarSet` mkUnVarSet vs
=====================================
compiler/GHC/Types/Unique/FM.hs
=====================================
@@ -51,7 +51,9 @@ module GHC.Types.Unique.FM (
delListFromUFM,
delListFromUFM_Directly,
plusUFM,
+ strictPlusUFM,
plusUFM_C,
+ strictPlusUFM_C,
plusUFM_CD,
plusUFM_CD2,
mergeUFM,
@@ -261,16 +263,24 @@ delListFromUFM_Directly = foldl' delFromUFM_Directly
delFromUFM_Directly :: UniqFM key elt -> Unique -> UniqFM key elt
delFromUFM_Directly (UFM m) u = UFM (M.delete (getKey u) m)
--- Bindings in right argument shadow those in the left
+-- | Bindings in right argument shadow those in the left.
+--
+-- Unlike containers this union is right-biased for historic reasons.
plusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt
--- M.union is left-biased, plusUFM should be right-biased.
plusUFM (UFM x) (UFM y) = UFM (M.union y x)
-- Note (M.union y x), with arguments flipped
-- M.union is left-biased, plusUFM should be right-biased.
+-- | Right biased
+strictPlusUFM :: UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM (UFM x) (UFM y) = UFM (MS.union y x)
+
plusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
plusUFM_C f (UFM x) (UFM y) = UFM (M.unionWith f x y)
+strictPlusUFM_C :: (elt -> elt -> elt) -> UniqFM key elt -> UniqFM key elt -> UniqFM key elt
+strictPlusUFM_C f (UFM x) (UFM y) = UFM (MS.unionWith f x y)
+
-- | `plusUFM_CD f m1 d1 m2 d2` merges the maps using `f` as the
-- combinding function and `d1` resp. `d2` as the default value if
-- there is no entry in `m1` reps. `m2`. The domain is the union of
=====================================
compiler/GHC/Types/Var/Env.hs
=====================================
@@ -12,7 +12,8 @@ module GHC.Types.Var.Env (
elemVarEnv, disjointVarEnv, anyVarEnv,
extendVarEnv, extendVarEnv_C, extendVarEnv_Acc,
extendVarEnvList,
- plusVarEnv, plusVarEnv_C, plusVarEnv_CD, plusMaybeVarEnv_C,
+ strictPlusVarEnv, plusVarEnv, plusVarEnv_C, strictPlusVarEnv_C,
+ plusVarEnv_CD, plusMaybeVarEnv_C,
plusVarEnvList, alterVarEnv,
delVarEnvList, delVarEnv,
minusVarEnv,
@@ -511,6 +512,7 @@ extendVarEnv :: VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_C :: (a->a->a) -> VarEnv a -> Var -> a -> VarEnv a
extendVarEnv_Acc :: (a->b->b) -> (a->b) -> VarEnv b -> Var -> a -> VarEnv b
plusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv :: VarEnv a -> VarEnv a -> VarEnv a
plusVarEnvList :: [VarEnv a] -> VarEnv a
extendVarEnvList :: VarEnv a -> [(Var, a)] -> VarEnv a
varEnvDomain :: VarEnv elt -> UnVarSet
@@ -522,6 +524,7 @@ delVarEnvList :: Foldable f => VarEnv a -> f Var -> VarEnv a
delVarEnv :: VarEnv a -> Var -> VarEnv a
minusVarEnv :: VarEnv a -> VarEnv b -> VarEnv a
plusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
+strictPlusVarEnv_C :: (a -> a -> a) -> VarEnv a -> VarEnv a -> VarEnv a
plusVarEnv_CD :: (a -> a -> a) -> VarEnv a -> a -> VarEnv a -> a -> VarEnv a
plusMaybeVarEnv_C :: (a -> a -> Maybe a) -> VarEnv a -> VarEnv a -> VarEnv a
mapVarEnv :: (a -> b) -> VarEnv a -> VarEnv b
@@ -548,6 +551,7 @@ extendVarEnv_C = addToUFM_C
extendVarEnv_Acc = addToUFM_Acc
extendVarEnvList = addListToUFM
plusVarEnv_C = plusUFM_C
+strictPlusVarEnv_C = strictPlusUFM_C
plusVarEnv_CD = plusUFM_CD
plusMaybeVarEnv_C = plusMaybeUFM_C
delVarEnvList = delListFromUFM
@@ -556,6 +560,7 @@ delVarEnvList = delListFromUFM
delVarEnv = delFromUFM
minusVarEnv = minusUFM
plusVarEnv = plusUFM
+strictPlusVarEnv = strictPlusUFM
plusVarEnvList = plusUFMList
-- lookupVarEnv is very hot (in part due to being called by substTyVar),
-- if it's not inlined than the mere allocation of the Just constructor causes
=====================================
testsuite/tests/perf/compiler/T26425.hs
=====================================
@@ -0,0 +1,514 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+module Reproducer (strToInt) where
+
+import qualified Data.Text as T
+
+{- This program results in a nested chain of join points and cases which tests
+ primarily OccAnal and Unfolding performance.
+-}
+
+strToInt :: T.Text -> Maybe Int
+strToInt txt = case txt of
+ "0" -> Just 0
+ "1" -> Just 1
+ "2" -> Just 2
+ "3" -> Just 3
+ "4" -> Just 4
+ "5" -> Just 5
+ "6" -> Just 6
+ "7" -> Just 7
+ "8" -> Just 8
+ "9" -> Just 9
+ "10" -> Just 10
+ "11" -> Just 11
+ "12" -> Just 12
+ "13" -> Just 13
+ "14" -> Just 14
+ "15" -> Just 15
+ "16" -> Just 16
+ "17" -> Just 17
+ "18" -> Just 18
+ "19" -> Just 19
+ "20" -> Just 20
+ "21" -> Just 21
+ "22" -> Just 22
+ "23" -> Just 23
+ "24" -> Just 24
+ "25" -> Just 25
+ "26" -> Just 26
+ "27" -> Just 27
+ "28" -> Just 28
+ "29" -> Just 29
+ "30" -> Just 30
+ "31" -> Just 31
+ "32" -> Just 32
+ "33" -> Just 33
+ "34" -> Just 34
+ "35" -> Just 35
+ "36" -> Just 36
+ "37" -> Just 37
+ "38" -> Just 38
+ "39" -> Just 39
+ "40" -> Just 40
+ "41" -> Just 41
+ "42" -> Just 42
+ "43" -> Just 43
+ "44" -> Just 44
+ "45" -> Just 45
+ "46" -> Just 46
+ "47" -> Just 47
+ "48" -> Just 48
+ "49" -> Just 49
+ "50" -> Just 50
+ "51" -> Just 51
+ "52" -> Just 52
+ "53" -> Just 53
+ "54" -> Just 54
+ "55" -> Just 55
+ "56" -> Just 56
+ "57" -> Just 57
+ "58" -> Just 58
+ "59" -> Just 59
+ "60" -> Just 60
+ "61" -> Just 61
+ "62" -> Just 62
+ "63" -> Just 63
+ "64" -> Just 64
+ "65" -> Just 65
+ "66" -> Just 66
+ "67" -> Just 67
+ "68" -> Just 68
+ "69" -> Just 69
+ "70" -> Just 70
+ "71" -> Just 71
+ "72" -> Just 72
+ "73" -> Just 73
+ "74" -> Just 74
+ "75" -> Just 75
+ "76" -> Just 76
+ "77" -> Just 77
+ "78" -> Just 78
+ "79" -> Just 79
+ "80" -> Just 80
+ "81" -> Just 81
+ "82" -> Just 82
+ "83" -> Just 83
+ "84" -> Just 84
+ "85" -> Just 85
+ "86" -> Just 86
+ "87" -> Just 87
+ "88" -> Just 88
+ "89" -> Just 89
+ "90" -> Just 90
+ "91" -> Just 91
+ "92" -> Just 92
+ "93" -> Just 93
+ "94" -> Just 94
+ "95" -> Just 95
+ "96" -> Just 96
+ "97" -> Just 97
+ "98" -> Just 98
+ "99" -> Just 99
+ "100" -> Just 100
+ "101" -> Just 101
+ "102" -> Just 102
+ "103" -> Just 103
+ "104" -> Just 104
+ "105" -> Just 105
+ "106" -> Just 106
+ "107" -> Just 107
+ "108" -> Just 108
+ "109" -> Just 109
+ "110" -> Just 110
+ "111" -> Just 111
+ "112" -> Just 112
+ "113" -> Just 113
+ "114" -> Just 114
+ "115" -> Just 115
+ "116" -> Just 116
+ "117" -> Just 117
+ "118" -> Just 118
+ "119" -> Just 119
+ "120" -> Just 120
+ "121" -> Just 121
+ "122" -> Just 122
+ "123" -> Just 123
+ "124" -> Just 124
+ "125" -> Just 125
+ "126" -> Just 126
+ "127" -> Just 127
+ "128" -> Just 128
+ "129" -> Just 129
+ "130" -> Just 130
+ "131" -> Just 131
+ "132" -> Just 132
+ "133" -> Just 133
+ "134" -> Just 134
+ "135" -> Just 135
+ "136" -> Just 136
+ "137" -> Just 137
+ "138" -> Just 138
+ "139" -> Just 139
+ "140" -> Just 140
+ "141" -> Just 141
+ "142" -> Just 142
+ "143" -> Just 143
+ "144" -> Just 144
+ "145" -> Just 145
+ "146" -> Just 146
+ "147" -> Just 147
+ "148" -> Just 148
+ "149" -> Just 149
+ "150" -> Just 150
+ "151" -> Just 151
+ "152" -> Just 152
+ "153" -> Just 153
+ "154" -> Just 154
+ "155" -> Just 155
+ "156" -> Just 156
+ "157" -> Just 157
+ "158" -> Just 158
+ "159" -> Just 159
+ "160" -> Just 160
+ "161" -> Just 161
+ "162" -> Just 162
+ "163" -> Just 163
+ "164" -> Just 164
+ "165" -> Just 165
+ "166" -> Just 166
+ "167" -> Just 167
+ "168" -> Just 168
+ "169" -> Just 169
+ "170" -> Just 170
+ "171" -> Just 171
+ "172" -> Just 172
+ "173" -> Just 173
+ "174" -> Just 174
+ "175" -> Just 175
+ "176" -> Just 176
+ "177" -> Just 177
+ "178" -> Just 178
+ "179" -> Just 179
+ "180" -> Just 180
+ "181" -> Just 181
+ "182" -> Just 182
+ "183" -> Just 183
+ "184" -> Just 184
+ "185" -> Just 185
+ "186" -> Just 186
+ "187" -> Just 187
+ "188" -> Just 188
+ "189" -> Just 189
+ "190" -> Just 190
+ "191" -> Just 191
+ "192" -> Just 192
+ "193" -> Just 193
+ "194" -> Just 194
+ "195" -> Just 195
+ "196" -> Just 196
+ "197" -> Just 197
+ "198" -> Just 198
+ "199" -> Just 199
+ "200" -> Just 200
+ "201" -> Just 201
+ "202" -> Just 202
+ "203" -> Just 203
+ "204" -> Just 204
+ "205" -> Just 205
+ "206" -> Just 206
+ "207" -> Just 207
+ "208" -> Just 208
+ "209" -> Just 209
+ "210" -> Just 210
+ "211" -> Just 211
+ "212" -> Just 212
+ "213" -> Just 213
+ "214" -> Just 214
+ "215" -> Just 215
+ "216" -> Just 216
+ "217" -> Just 217
+ "218" -> Just 218
+ "219" -> Just 219
+ "220" -> Just 220
+ "221" -> Just 221
+ "222" -> Just 222
+ "223" -> Just 223
+ "224" -> Just 224
+ "225" -> Just 225
+ "226" -> Just 226
+ "227" -> Just 227
+ "228" -> Just 228
+ "229" -> Just 229
+ "230" -> Just 230
+ "231" -> Just 231
+ "232" -> Just 232
+ "233" -> Just 233
+ "234" -> Just 234
+ "235" -> Just 235
+ "236" -> Just 236
+ "237" -> Just 237
+ "238" -> Just 238
+ "239" -> Just 239
+ "240" -> Just 240
+ "241" -> Just 241
+ "242" -> Just 242
+ "243" -> Just 243
+ "244" -> Just 244
+ "245" -> Just 245
+ "246" -> Just 246
+ "247" -> Just 247
+ "248" -> Just 248
+ "249" -> Just 249
+ "250" -> Just 250
+ "251" -> Just 251
+ "252" -> Just 252
+ "253" -> Just 253
+ "254" -> Just 254
+ "255" -> Just 255
+ "256" -> Just 256
+ "257" -> Just 257
+ "258" -> Just 258
+ "259" -> Just 259
+ "260" -> Just 260
+ "261" -> Just 261
+ "262" -> Just 262
+ "263" -> Just 263
+ "264" -> Just 264
+ "265" -> Just 265
+ "266" -> Just 266
+ "267" -> Just 267
+ "268" -> Just 268
+ "269" -> Just 269
+ "270" -> Just 270
+ "271" -> Just 271
+ "272" -> Just 272
+ "273" -> Just 273
+ "274" -> Just 274
+ "275" -> Just 275
+ "276" -> Just 276
+ "277" -> Just 277
+ "278" -> Just 278
+ "279" -> Just 279
+ "280" -> Just 280
+ "281" -> Just 281
+ "282" -> Just 282
+ "283" -> Just 283
+ "284" -> Just 284
+ "285" -> Just 285
+ "286" -> Just 286
+ "287" -> Just 287
+ "288" -> Just 288
+ "289" -> Just 289
+ "290" -> Just 290
+ "291" -> Just 291
+ "292" -> Just 292
+ "293" -> Just 293
+ "294" -> Just 294
+ "295" -> Just 295
+ "296" -> Just 296
+ "297" -> Just 297
+ "298" -> Just 298
+ "299" -> Just 299
+ "300" -> Just 300
+ "301" -> Just 301
+ "302" -> Just 302
+ "303" -> Just 303
+ "304" -> Just 304
+ "305" -> Just 305
+ "306" -> Just 306
+ "307" -> Just 307
+ "308" -> Just 308
+ "309" -> Just 309
+ "310" -> Just 310
+ "311" -> Just 311
+ "312" -> Just 312
+ "313" -> Just 313
+ "314" -> Just 314
+ "315" -> Just 315
+ "316" -> Just 316
+ "317" -> Just 317
+ "318" -> Just 318
+ "319" -> Just 319
+ "320" -> Just 320
+ "321" -> Just 321
+ "322" -> Just 322
+ "323" -> Just 323
+ "324" -> Just 324
+ "325" -> Just 325
+ "326" -> Just 326
+ "327" -> Just 327
+ "328" -> Just 328
+ "329" -> Just 329
+ "330" -> Just 330
+ "331" -> Just 331
+ "332" -> Just 332
+ "333" -> Just 333
+ "334" -> Just 334
+ "335" -> Just 335
+ "336" -> Just 336
+ "337" -> Just 337
+ "338" -> Just 338
+ "339" -> Just 339
+ "340" -> Just 340
+ "341" -> Just 341
+ "342" -> Just 342
+ "343" -> Just 343
+ "344" -> Just 344
+ "345" -> Just 345
+ "346" -> Just 346
+ "347" -> Just 347
+ "348" -> Just 348
+ "349" -> Just 349
+ "350" -> Just 350
+ "351" -> Just 351
+ "352" -> Just 352
+ "353" -> Just 353
+ "354" -> Just 354
+ "355" -> Just 355
+ "356" -> Just 356
+ "357" -> Just 357
+ "358" -> Just 358
+ "359" -> Just 359
+ "360" -> Just 360
+ "361" -> Just 361
+ "362" -> Just 362
+ "363" -> Just 363
+ "364" -> Just 364
+ "365" -> Just 365
+ "366" -> Just 366
+ "367" -> Just 367
+ "368" -> Just 368
+ "369" -> Just 369
+ "370" -> Just 370
+ "371" -> Just 371
+ "372" -> Just 372
+ "373" -> Just 373
+ "374" -> Just 374
+ "375" -> Just 375
+ "376" -> Just 376
+ "377" -> Just 377
+ "378" -> Just 378
+ "379" -> Just 379
+ "380" -> Just 380
+ "381" -> Just 381
+ "382" -> Just 382
+ "383" -> Just 383
+ "384" -> Just 384
+ "385" -> Just 385
+ "386" -> Just 386
+ "387" -> Just 387
+ "388" -> Just 388
+ "389" -> Just 389
+ "390" -> Just 390
+ "391" -> Just 391
+ "392" -> Just 392
+ "393" -> Just 393
+ "394" -> Just 394
+ "395" -> Just 395
+ "396" -> Just 396
+ "397" -> Just 397
+ "398" -> Just 398
+ "399" -> Just 399
+ "400" -> Just 400
+ "401" -> Just 401
+ "402" -> Just 402
+ "403" -> Just 403
+ "404" -> Just 404
+ "405" -> Just 405
+ "406" -> Just 406
+ "407" -> Just 407
+ "408" -> Just 408
+ "409" -> Just 409
+ "410" -> Just 410
+ "411" -> Just 411
+ "412" -> Just 412
+ "413" -> Just 413
+ "414" -> Just 414
+ "415" -> Just 415
+ "416" -> Just 416
+ "417" -> Just 417
+ "418" -> Just 418
+ "419" -> Just 419
+ "420" -> Just 420
+ "421" -> Just 421
+ "422" -> Just 422
+ "423" -> Just 423
+ "424" -> Just 424
+ "425" -> Just 425
+ "426" -> Just 426
+ "427" -> Just 427
+ "428" -> Just 428
+ "429" -> Just 429
+ "430" -> Just 430
+ "431" -> Just 431
+ "432" -> Just 432
+ "433" -> Just 433
+ "434" -> Just 434
+ "435" -> Just 435
+ "436" -> Just 436
+ "437" -> Just 437
+ "438" -> Just 438
+ "439" -> Just 439
+ "440" -> Just 440
+ "441" -> Just 441
+ "442" -> Just 442
+ "443" -> Just 443
+ "444" -> Just 444
+ "445" -> Just 445
+ "446" -> Just 446
+ "447" -> Just 447
+ "448" -> Just 448
+ "449" -> Just 449
+ "450" -> Just 450
+ "451" -> Just 451
+ "452" -> Just 452
+ "453" -> Just 453
+ "454" -> Just 454
+ "455" -> Just 455
+ "456" -> Just 456
+ "457" -> Just 457
+ "458" -> Just 458
+ "459" -> Just 459
+ "460" -> Just 460
+ "461" -> Just 461
+ "462" -> Just 462
+ "463" -> Just 463
+ "464" -> Just 464
+ "465" -> Just 465
+ "466" -> Just 466
+ "467" -> Just 467
+ "468" -> Just 468
+ "469" -> Just 469
+ "470" -> Just 470
+ "471" -> Just 471
+ "472" -> Just 472
+ "473" -> Just 473
+ "474" -> Just 474
+ "475" -> Just 475
+ "476" -> Just 476
+ "477" -> Just 477
+ "478" -> Just 478
+ "479" -> Just 479
+ "480" -> Just 480
+ "481" -> Just 481
+ "482" -> Just 482
+ "483" -> Just 483
+ "484" -> Just 484
+ "485" -> Just 485
+ "486" -> Just 486
+ "487" -> Just 487
+ "488" -> Just 488
+ "489" -> Just 489
+ "490" -> Just 490
+ "491" -> Just 491
+ "492" -> Just 492
+ "493" -> Just 493
+ "494" -> Just 494
+ "495" -> Just 495
+ "496" -> Just 496
+ "497" -> Just 497
+ "498" -> Just 498
+ "499" -> Just 499
+ "500" -> Just 500
+ _ -> Nothing
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -806,3 +806,8 @@ test('interpreter_steplocal',
],
ghci_script,
['interpreter_steplocal.script'])
+
+test ('T26425',
+ [ collect_compiler_stats('all',5) ],
+ compile,
+ ['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6812d21ffad0bd78f1522dfa76b825…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6812d21ffad0bd78f1522dfa76b825…
You're receiving this email because of your account on gitlab.haskell.org.
1
0
[Git][ghc/ghc][wip/ani/kill-popErrCtxt] match context with record updates dont get added in error context
by Apoorv Ingle (@ani) 27 Oct '25
by Apoorv Ingle (@ani) 27 Oct '25
27 Oct '25
Apoorv Ingle pushed to branch wip/ani/kill-popErrCtxt at Glasgow Haskell Compiler / GHC
Commits:
f782a81c by Apoorv Ingle at 2025-10-27T12:10:33-05:00
match context with record updates dont get added in error context
- - - - -
1 changed file:
- compiler/GHC/Tc/Gen/Match.hs
Changes:
=====================================
compiler/GHC/Tc/Gen/Match.hs
=====================================
@@ -331,6 +331,7 @@ tcMatch tc_body pat_tys rhs_ty match
add_match_ctxt thing_inside = case ctxt of
LamAlt LamSingle -> thing_inside
StmtCtxt (HsDoStmt{}) -> thing_inside -- this is an expanded do stmt
+ RecUpd -> thing_inside -- record update is Expanded out so ignore it
_ -> addErrCtxt (MatchInCtxt match) thing_inside
-------------
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f782a81c376019de8a50b0e10d310bc…
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f782a81c376019de8a50b0e10d310bc…
You're receiving this email because of your account on gitlab.haskell.org.
1
0