[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Revert "compiler: start deprecating cmmToRawCmmHook"
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Oct 18 17:43:24 UTC 2024
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
525d451e by Cheng Shao at 2024-10-17T23:03:34-04:00
Revert "compiler: start deprecating cmmToRawCmmHook"
This reverts commit 1c064ef1f3e1aa2afc996e962ad53effa99ec5f4. Turns
out the GHC-WPC project does use it to observe Cmm in the pipeline,
see #25363.
- - - - -
5bcfefd5 by Cheng Shao at 2024-10-17T23:04:09-04:00
rts: fix pointer overflow undefined behavior in bytecode interpreter
This patch fixes an unnoticed undefined behavior in the bytecode
interpreter. It can be caught by building `rts/Interpreter.c` with
`-fsanitize=pointer-overflow`, the warning message is something like:
```
rts/Interpreter.c:1369:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1369:13
rts/Interpreter.c:1265:13: runtime error: addition of unsigned offset to 0x004200197660 overflowed to 0x004200197658
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1265:13
rts/Interpreter.c:1645:13: runtime error: addition of unsigned offset to 0x0042000b22f8 overflowed to 0x0042000b22f0
SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Interpreter.c:1645:13
```
Whenever we do something like `SpW(-1)`, the negative argument is
implicitly converted to an unsigned integer type and causes pointer
arithmetic overflow. It happens to be harmless for most targets since
overflowing would wrap the result to desired value, but it's still
coincidental and undefined behavior. Furthermore, it causes real
damage to the wasm backend, given clang-20 will emit invalid wasm code
that crashes at run-time for this kind of C code! (see
https://github.com/llvm/llvm-project/issues/108770)
The fix here is adding some explicit casts to ensure we always use the
signed `ptrdiff_t` type as right hand operand of pointer arithmetic.
- - - - -
eb67875f by Matthew Craven at 2024-10-18T12:18:35+00:00
Bump transformers submodule
The svg image files mentioned in transformers.cabal were
previously not checked in, which broke sdist generation.
- - - - -
366a1109 by Matthew Craven at 2024-10-18T12:18:35+00:00
Remove reference to non-existent file in haddock.cabal
- - - - -
826852e9 by Matthew Craven at 2024-10-18T12:18:35+00:00
Move tests T11462 and T11525 into tests/tcplugins
- - - - -
dbe27152 by Matthew Craven at 2024-10-18T12:18:35+00:00
Repair the 'build-cabal' hadrian target
Fixes #23117. Fixes #23281. Fixes #23490.
This required:
* Updating the bit-rotted compiler/Setup.hs and its setup-depends
* Listing a few recently-added libraries and utilities
in cabal.project-reinstall
* Setting allow-boot-library-installs to 'True' since Cabal
now considers the 'ghc' package itself a boot library for
the purposes of this flag
Additionally, the allow-newer block in cabal.project-reinstall
was removed. This block was probably added because when the
libraries/Cabal submodule is too new relative to the cabal-install
executable, solving the setup-depends for any package with a custom
setup requires building an old Cabal (from Hackage) against the
in-tree version of base, and this can fail un-necessarily due to
tight version bounds on base. However, the blind allow-newer can
also cause the solver to go berserk and choose a stupid build plan
that has no business succeeding, and the failures when this happens
are dreadfully confusing. (See #23281 and #24363.)
Why does setup-depends solving insist on an old version of Cabal? See:
https://github.com/haskell/cabal/blob/0a0b33983b0f022b9697f7df3a69358ee9061a89/cabal-install/src/Distribution/Client/ProjectPlanning.hs#L1393-L1410
The right solution here is probably to use the in-tree cabal-install
from libraries/Cabal/cabal-install with the build-cabal target rather
than whatever the environment happens to provide. But this is left
for future work.
- - - - -
b3c00c62 by Matthew Craven at 2024-10-18T12:18:35+00:00
Revert "CI: Disable the test-cabal-reinstall job"
This reverts commit 38c3afb64d3ffc42f12163c6f0f0d5c414aa8255.
- - - - -
147f8f01 by Daneel Yaitskov at 2024-10-18T13:43:12-04:00
base: speed up traceEventIO and friends when eventlogging is turned off #17949
Check the RTS flag before doing any work with the given lazy string.
Fix #17949
Co-authored-by: Michael Peyton Jones <me at michaelpj.com>
Co-authored-by: Sylvain Henry <sylvain at haskus.fr>
Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>
- - - - -
23 changed files:
- .gitlab-ci.yml
- cabal.project-reinstall
- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/Driver/Main.hs
- compiler/Setup.hs
- compiler/ghc.cabal.in
- libraries/base/changelog.md
- libraries/ghc-internal/ghc-internal.cabal.in
- libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
- libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
- + libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
- libraries/transformers
- rts/Interpreter.c
- + testsuite/tests/perf/should_run/T17949.hs
- testsuite/tests/perf/should_run/all.T
- testsuite/tests/profiling/should_run/callstack002.stderr
- testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs
- testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs
- testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs
- testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs
- testsuite/tests/tcplugins/all.T
- testsuite/tests/typecheck/should_compile/all.T
- utils/haddock/haddock.cabal
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -494,21 +494,16 @@ stack-hadrian-build:
# Testing reinstallable ghc codepath
####################################
-# As documented on the original ticket #19896, this feature already has a long
-# way to go before it can actually be used. Meanwhile, parts of it have
-# bit-rotted, possibly related to some Cabal change. The job is disabled for
-# now.
-#
-# test-cabal-reinstall-x86_64-linux-deb10:
-# extends: nightly-x86_64-linux-deb10-validate
-# stage: full-build
-# variables:
-# REINSTALL_GHC: "yes"
-# BUILD_FLAVOUR: validate
-# TEST_ENV: "x86_64-linux-deb10-cabal-install"
-# rules:
-# - if: $NIGHTLY
-# - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/'
+test-cabal-reinstall-x86_64-linux-deb10:
+ extends: nightly-x86_64-linux-deb10-validate
+ stage: full-build
+ variables:
+ REINSTALL_GHC: "yes"
+ BUILD_FLAVOUR: validate
+ TEST_ENV: "x86_64-linux-deb10-cabal-install"
+ rules:
+ - if: $NIGHTLY
+ - if: '$CI_MERGE_REQUEST_LABELS =~ /.*test-reinstall.*/'
########################################
# Testing ABI is invariant across builds
=====================================
cabal.project-reinstall
=====================================
@@ -12,11 +12,13 @@ packages: ./compiler
-- ./libraries/deepseq/
./libraries/directory/
./libraries/exceptions/
+ ./libraries/file-io/
./libraries/filepath/
-- ./libraries/ghc-bignum/
./libraries/ghc-boot/
-- ./libraries/ghc-boot-th/
./libraries/ghc-compact
+ ./libraries/ghc-experimental
./libraries/ghc-heap
./libraries/ghci
-- ./libraries/ghc-prim
@@ -25,6 +27,7 @@ packages: ./compiler
./libraries/hpc
-- ./libraries/integer-gmp
./libraries/mtl/
+ ./libraries/os-string/
./libraries/parsec/
-- ./libraries/pretty/
./libraries/process/
@@ -39,7 +42,11 @@ packages: ./compiler
./libraries/Win32/
./libraries/xhtml/
./utils/ghc-pkg
+ ./utils/ghc-toolchain
+ ./utils/ghc-toolchain/exe
./utils/haddock
+ ./utils/haddock/haddock-api
+ ./utils/haddock/haddock-library
./utils/hp2ps
./utils/hpc
./utils/hsc2hs
@@ -61,15 +68,10 @@ constraints: ghc +internal-interpreter +dynamic-system-linke,
any.pretty installed,
any.template-haskell installed
-allow-newer:
- ghc-paths:Cabal,
- *:base,
- *:ghc-prim,
- tree-diff:time
benchmarks: False
tests: False
-allow-boot-library-installs: False
+allow-boot-library-installs: True
-- Workaround for https://github.com/haskell/cabal/issues/7297
package *
=====================================
compiler/GHC/Driver/Hooks.hs
=====================================
@@ -154,8 +154,6 @@ data Hooks = Hooks
-> IO (CgStream RawCmmGroup a)))
}
-{-# DEPRECATED cmmToRawCmmHook "cmmToRawCmmHook is being deprecated. If you do use it in your project, please raise a GHC issue!" #-}
-
class HasHooks m where
getHooks :: m Hooks
=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -5,9 +5,6 @@
{-# OPTIONS_GHC -fprof-auto-top #-}
--- Remove this after cmmToRawCmmHook removal
-{-# OPTIONS_GHC -Wno-deprecations #-}
-
-------------------------------------------------------------------------------
--
-- | Main API for compiling plain Haskell source code.
=====================================
compiler/Setup.hs
=====================================
@@ -1,4 +1,4 @@
-{-# LANGUAGE RecordWildCards #-}
+{-# LANGUAGE NamedFieldPuns #-}
module Main where
import Distribution.Simple
@@ -52,10 +52,12 @@ primopIncls =
, ("primop-vector-tys-exports.hs-incl", "--primop-vector-tys-exports")
, ("primop-vector-tycons.hs-incl" , "--primop-vector-tycons")
, ("primop-docs.hs-incl" , "--wired-in-docs")
+ , ("primop-deprecations.hs-incl" , "--wired-in-deprecations")
]
ghcAutogen :: Verbosity -> LocalBuildInfo -> IO ()
-ghcAutogen verbosity lbi at LocalBuildInfo{..} = do
+ghcAutogen verbosity lbi at LocalBuildInfo{pkgDescrFile,withPrograms,componentNameMap}
+ = do
-- Get compiler/ root directory from the cabal file
let Just compilerRoot = takeDirectory <$> pkgDescrFile
@@ -77,7 +79,7 @@ ghcAutogen verbosity lbi at LocalBuildInfo{..} = do
-- Call genprimopcode to generate *.hs-incl
forM_ primopIncls $ \(file,command) -> do
contents <- readProcess "genprimopcode" [command] primopsStr
- rewriteFileEx verbosity (buildDir </> file) contents
+ rewriteFileEx verbosity (buildDir lbi </> file) contents
-- Write GHC.Platform.Constants
let platformConstantsPath = autogenPackageModulesDir lbi </> "GHC/Platform/Constants.hs"
=====================================
compiler/ghc.cabal.in
=====================================
@@ -50,7 +50,7 @@ extra-source-files:
custom-setup
- setup-depends: base >= 3 && < 5, Cabal >= 1.6 && <3.10, directory, process, filepath, containers
+ setup-depends: base >= 3 && < 5, Cabal >= 1.6 && <3.14, directory, process, filepath, containers
Flag internal-interpreter
Description: Build with internal interpreter support.
=====================================
libraries/base/changelog.md
=====================================
@@ -37,6 +37,7 @@
for libraries that define exception-handling combinators like `catch` and
`onException`, such as `base`, or the `exceptions` package.
* Move `Lift ByteArray` and `Lift Fixed` instances into `base` from `template-haskell`. See [CLC proposal #287](https://github.com/haskell/core-libraries-committee/issues/287).
+ * Make `Debug.Trace.{traceEventIO,traceMarkerIO}` faster when tracing is disabled. See [CLC proposal #291](https://github.com/haskell/core-libraries-committee/issues/291).
## 4.20.0.0 May 2024
* Shipped with GHC 9.10.1
=====================================
libraries/ghc-internal/ghc-internal.cabal.in
=====================================
@@ -253,6 +253,7 @@ Library
GHC.Internal.Records
GHC.Internal.ResponseFile
GHC.Internal.RTS.Flags
+ GHC.Internal.RTS.Flags.Test
GHC.Internal.ST
GHC.Internal.Stack.CloneStack
GHC.Internal.StaticPtr
=====================================
libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs
=====================================
@@ -1,4 +1,5 @@
{-# LANGUAGE Unsafe #-}
+{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE UnboxedTuples #-}
@@ -54,6 +55,11 @@ import GHC.Internal.Ptr
import GHC.Internal.Show
import GHC.Internal.Stack
import GHC.Internal.Data.List (null, partition)
+import GHC.Internal.RTS.Flags.Test
+
+-- | 'userEventTracingEnabled' is True if event logging for user events (@+RTS -l@) is enabled.
+userEventTracingEnabled :: IO Bool
+userEventTracingEnabled = getUserEventTracingEnabled
-- | The 'traceIO' function outputs the trace message from the IO monad.
-- This sequences the output with respect to other IO actions.
@@ -239,8 +245,8 @@ traceStack str expr = unsafePerformIO $ do
{-# NOINLINE traceEvent #-}
-- | The 'traceEvent' function behaves like 'trace' with the difference that
--- the message is emitted to the eventlog, if eventlog profiling is available
--- and enabled at runtime.
+-- the message is emitted to the eventlog, if eventlog tracing is available
+-- and user event tracing is enabled at runtime.
--
-- It is suitable for use in pure code. In an IO context use 'traceEventIO'
-- instead.
@@ -256,16 +262,19 @@ traceEvent msg expr = unsafeDupablePerformIO $ do
return expr
-- | The 'traceEventIO' function emits a message to the eventlog, if eventlog
--- profiling is available and enabled at runtime.
+-- tracing is available and user event tracing is enabled at runtime.
--
-- Compared to 'traceEvent', 'traceEventIO' sequences the event with respect to
-- other IO actions.
--
-- @since base-4.5.0.0
traceEventIO :: String -> IO ()
-traceEventIO msg =
- Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
- case traceEvent# p s of s' -> (# s', () #)
+{-# INLINE traceEventIO #-}
+traceEventIO msg = do
+ enabled <- userEventTracingEnabled
+ when enabled $
+ Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+ case traceEvent# p s of s' -> (# s', () #)
-- | Like 'traceEvent', but emits the result of calling a function on its
-- argument.
@@ -276,7 +285,7 @@ traceEventWith f a = traceEvent (f a) a
{-# NOINLINE traceMarker #-}
-- | The 'traceMarker' function emits a marker to the eventlog, if eventlog
--- profiling is available and enabled at runtime. The @String@ is the name of
+-- tracing is available and enabled at runtime. The @String@ is the name of
-- the marker. The name is just used in the profiling tools to help you keep
-- clear which marker is which.
--
@@ -294,16 +303,19 @@ traceMarker msg expr = unsafeDupablePerformIO $ do
return expr
-- | The 'traceMarkerIO' function emits a marker to the eventlog, if eventlog
--- profiling is available and enabled at runtime.
+-- tracing is available and user event tracing is enabled at runtime.
--
-- Compared to 'traceMarker', 'traceMarkerIO' sequences the event with respect to
-- other IO actions.
--
-- @since base-4.7.0.0
traceMarkerIO :: String -> IO ()
-traceMarkerIO msg =
- Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
- case traceMarker# p s of s' -> (# s', () #)
+{-# INLINE traceMarkerIO #-}
+traceMarkerIO msg = do
+ enabled <- userEventTracingEnabled
+ when enabled $
+ Enc.withCString utf8 msg $ \(Ptr p) -> IO $ \s ->
+ case traceMarker# p s of s' -> (# s', () #)
-- | Immediately flush the event log, if enabled.
--
=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc
=====================================
@@ -613,6 +613,10 @@ getProfFlags = do
getTraceFlags :: IO TraceFlags
getTraceFlags = do
+#if defined(javascript_HOST_ARCH)
+ -- The JS backend does not currently have trace flags
+ pure (TraceFlags TraceNone False False False False False False False)
+#else
let ptr = (#ptr RTS_FLAGS, TraceFlags) rtsFlagsPtr
TraceFlags <$> (toEnum . fromIntegral
<$> (#{peek TRACE_FLAGS, tracing} ptr :: IO CInt))
@@ -630,6 +634,7 @@ getTraceFlags = do
(#{peek TRACE_FLAGS, sparks_full} ptr :: IO CBool))
<*> (toBool <$>
(#{peek TRACE_FLAGS, user} ptr :: IO CBool))
+#endif
getTickyFlags :: IO TickyFlags
getTickyFlags = do
=====================================
libraries/ghc-internal/src/GHC/Internal/RTS/Flags/Test.hsc
=====================================
@@ -0,0 +1,36 @@
+{-# LANGUAGE NoImplicitPrelude #-}
+
+-- | Module with fewer dependencies than GHC.Internal.RTS.Flags
+-- that allows to quickly test if some flag is set.
+module GHC.Internal.RTS.Flags.Test
+ ( getUserEventTracingEnabled
+ )
+where
+
+import GHC.Internal.Base
+
+#if !defined(javascript_HOST_ARCH)
+
+import GHC.Internal.Ptr
+import GHC.Internal.Foreign.C.Types
+import GHC.Internal.Foreign.Marshal.Utils
+import GHC.Internal.Foreign.Storable
+import GHC.Internal.Data.Functor ((<$>))
+
+#include "Rts.h"
+#include "rts/Flags.h"
+
+foreign import ccall "&RtsFlags" rtsFlagsPtr :: Ptr ()
+#endif
+
+-- | Specialized version of 'getTraceFlags' for just checking if user
+-- event tracing is enabled.
+getUserEventTracingEnabled :: IO Bool
+getUserEventTracingEnabled = do
+#if defined(javascript_HOST_ARCH)
+ -- The JS backend does not currently have trace flags
+ pure False
+#else
+ let ptr = (#ptr RTS_FLAGS, TraceFlags) rtsFlagsPtr
+ toBool <$> (#{peek TRACE_FLAGS, user} ptr :: IO CBool)
+#endif
=====================================
libraries/transformers
=====================================
@@ -1 +1 @@
-Subproject commit ba3503905dec072acc6515323c884706efd4dbb4
+Subproject commit b3eaaae9b6c986aaac84f0f05a137eef65ccfab3
=====================================
rts/Interpreter.c
=====================================
@@ -157,11 +157,11 @@ tag functions as tag inference currently doesn't rely on those being properly ta
cap->r.rRet = (retcode); \
return cap;
-#define Sp_plusB(n) ((void *)(((StgWord8*)Sp) + (n)))
-#define Sp_minusB(n) ((void *)(((StgWord8*)Sp) - (n)))
+#define Sp_plusB(n) ((void *)((StgWord8*)Sp + (ptrdiff_t)(n)))
+#define Sp_minusB(n) ((void *)((StgWord8*)Sp - (ptrdiff_t)(n)))
-#define Sp_plusW(n) (Sp_plusB((n) * sizeof(W_)))
-#define Sp_minusW(n) (Sp_minusB((n) * sizeof(W_)))
+#define Sp_plusW(n) (Sp_plusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
+#define Sp_minusW(n) (Sp_minusB((ptrdiff_t)(n) * (ptrdiff_t)sizeof(W_)))
#define Sp_addB(n) (Sp = Sp_plusB(n))
#define Sp_subB(n) (Sp = Sp_minusB(n))
=====================================
testsuite/tests/perf/should_run/T17949.hs
=====================================
@@ -0,0 +1,7 @@
+module Main where
+
+import Debug.Trace
+
+main :: IO ()
+main = do
+ traceEventIO (show [0..1234567])
=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -414,3 +414,4 @@ test('T21839r',
test('T18964', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O'])
test('T23021', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2'])
test('T25055', [collect_stats('bytes allocated', 2), only_ways(['normal'])], compile_and_run, ['-O2'])
+test('T17949', [collect_stats('bytes allocated', 1), only_ways(['normal'])], compile_and_run, ['-O2'])
=====================================
testsuite/tests/profiling/should_run/callstack002.stderr
=====================================
@@ -1,6 +1,6 @@
f: 42
CallStack (from -prof):
- GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:234:1-10)
+ GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:240:1-10)
Main.f (callstack002.hs:10:7-43)
Main.map.go (callstack002.hs:15:21-23)
Main.map.go (callstack002.hs:15:21-34)
@@ -9,7 +9,7 @@ CallStack (from -prof):
Main.CAF (<entire-module>)
f: 43
CallStack (from -prof):
- GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:234:1-10)
+ GHC.Internal.Debug.Trace.traceStack (libraries/ghc-internal/src/GHC/Internal/Debug/Trace.hs:240:1-10)
Main.f (callstack002.hs:10:7-43)
Main.map.go (callstack002.hs:15:21-23)
Main.map.go (callstack002.hs:15:21-34)
=====================================
testsuite/tests/typecheck/should_compile/T11462.hs → testsuite/tests/tcplugins/T11462.hs
=====================================
=====================================
testsuite/tests/typecheck/should_compile/T11462_Plugin.hs → testsuite/tests/tcplugins/T11462_Plugin.hs
=====================================
=====================================
testsuite/tests/typecheck/should_compile/T11525.hs → testsuite/tests/tcplugins/T11525.hs
=====================================
=====================================
testsuite/tests/typecheck/should_compile/T11525_Plugin.hs → testsuite/tests/tcplugins/T11525_Plugin.hs
=====================================
=====================================
testsuite/tests/tcplugins/all.T
=====================================
@@ -109,3 +109,10 @@ test('TcPlugin_CtId'
, [ 'TcPlugin_CtId.hs'
, '-dynamic -package ghc' if have_dynamic() else '-package ghc' ]
)
+
+test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
+ [None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
+ '-dynamic' if have_dynamic() else ''])
+test('T11525', [js_broken(22261), req_th, req_plugins], multi_compile,
+ [None, [('T11525_Plugin.hs', '-package ghc'), ('T11525.hs', '')],
+ '-dynamic' if have_dynamic() else ''])
=====================================
testsuite/tests/typecheck/should_compile/all.T
=====================================
@@ -500,9 +500,6 @@ test('T10592', normal, compile, [''])
test('T11305', normal, compile, [''])
test('T11254', normal, compile, [''])
test('T11379', normal, compile, [''])
-test('T11462', [js_broken(22261), req_th, req_plugins], multi_compile,
- [None, [('T11462_Plugin.hs', '-package ghc'), ('T11462.hs', '')],
- '-dynamic' if have_dynamic() else ''])
test('T11480', normal, compile, [''])
test('RebindHR', normal, compile, [''])
test('RebindNegate', normal, compile, [''])
@@ -568,9 +565,6 @@ test('T11723', normal, compile, [''])
test('T12987', normal, compile, [''])
test('T11736', normal, compile, [''])
test('T13248', expect_broken(13248), compile, [''])
-test('T11525', [js_broken(22261), req_th, req_plugins], multi_compile,
- [None, [('T11525_Plugin.hs', '-package ghc'), ('T11525.hs', '')],
- '-dynamic' if have_dynamic() else ''])
test('T12923_1', normal, compile, [''])
test('T21208', normal, compile, [''])
test('T12923_2', normal, compile, [''])
=====================================
utils/haddock/haddock.cabal
=====================================
@@ -43,7 +43,6 @@ extra-source-files:
doc/README.md
doc/*.rst
doc/conf.py
- haddock-api/src/haddock.sh
html-test/src/*.hs
html-test/ref/*.html
hypsrc-test/src/*.hs
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6dbcd8718a8d1ad37b06806b7c14d3e90445464...147f8f0176db0d777955648dd5fc6ecd32e82576
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6dbcd8718a8d1ad37b06806b7c14d3e90445464...147f8f0176db0d777955648dd5fc6ecd32e82576
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241018/150dad87/attachment-0001.html>
More information about the ghc-commits
mailing list