[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Update directory submodule to latest master
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Aug 20 01:06:42 UTC 2024
Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
47088840 by Matthew Pickering at 2024-08-19T21:06:26-04:00
Update directory submodule to latest master
The primary reason for this bump is to fix the warning from `ghc-pkg
check`:
```
Warning: include-dirs: /data/home/ubuntu/.ghcup/ghc/9.6.2/lib/ghc-9.6.2/lib/../lib/aarch64-linux-ghc-9.6.2/directory-1.3.8.1/include doesn't exist or isn't a directory
```
This also requires adding the `file-io` package as a boot library (which
is discussed in #25145)
Fixes #23594 #25145
- - - - -
590b60b8 by Cheng Shao at 2024-08-19T21:06:27-04:00
driver: bail out when -fllvm is passed to GHC not configured with LLVM
This patch makes GHC bail out with an proper error message when it's
not configured with LLVM but users attempt to pass -fllvm, see #25011
and added comment for details.
- - - - -
528a5992 by Mike Pilgrem at 2024-08-19T21:06:33-04:00
Fix #15773 Clarify further -rtsopts 'defaults' in docs
- - - - -
5418a034 by Sebastian Graf at 2024-08-19T21:06:33-04:00
Improve efficiency of `assertError` (#24625)
... by moving `lazy` to the exception-throwing branch.
It's all documented in `Note [Strictness of assertError]`.
- - - - -
12 changed files:
- .gitmodules
- compiler/GHC/SysTools/Tasks.hs
- docs/users_guide/9.12.1-notes.rst
- docs/users_guide/phases.rst
- hadrian/src/Packages.hs
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- libraries/directory
- + libraries/file-io
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
- + testsuite/tests/simplCore/should_compile/T24625.hs
- testsuite/tests/simplCore/should_compile/all.T
Changes:
=====================================
.gitmodules
=====================================
@@ -118,3 +118,6 @@
[submodule "hadrian/vendored/Cabal"]
path = hadrian/vendored/Cabal
url = https://gitlab.haskell.org/ghc/packages/Cabal.git
+[submodule "libraries/file-io"]
+ path = libraries/file-io
+ url = https://gitlab.haskell.org/ghc/packages/file-io.git
=====================================
compiler/GHC/SysTools/Tasks.hs
=====================================
@@ -28,6 +28,7 @@ import GHC.Utils.Logger
import GHC.Utils.TmpFs
import GHC.Utils.Panic
+import Control.Monad
import Data.List (tails, isPrefixOf)
import Data.Maybe (fromMaybe)
import System.IO
@@ -283,6 +284,26 @@ figureLlvmVersion logger dflags = traceSystoolCommand logger "llc" $ do
-- of the options they've specified. llc doesn't care what other
-- options are specified when '-version' is used.
args' = args ++ ["-version"]
+ -- Since !12001, when GHC is not configured with llc/opt with
+ -- supported version range, configure script will leave llc/opt
+ -- commands as blank in settings. In this case, we should bail out
+ -- with a proper error, see #25011.
+ --
+ -- Note that this does not make the -Wunsupported-llvm-version
+ -- warning logic redundant! Power users might want to use
+ -- -pgmlc/-pgmlo to override llc/opt locations to test LLVM outside
+ -- officially supported version range, and the driver will produce
+ -- the warning and carry on code generation.
+ when (null pgm) $ do
+ fatalErrorMsg logger $ vcat
+ [ text "Error:", nest 9 $
+ text "GHC was not configured with a supported LLVM toolchain" $$
+ text ("Make sure you have installed LLVM between ["
+ ++ llvmVersionStr supportedLlvmVersionLowerBound
+ ++ " and "
+ ++ llvmVersionStr supportedLlvmVersionUpperBound
+ ++ ") and reinstall GHC to make -fllvm work") ]
+ ghcExit logger 1
catchIO (do
(pin, pout, perr, p) <- runInteractiveProcess pgm args'
Nothing Nothing
=====================================
docs/users_guide/9.12.1-notes.rst
=====================================
@@ -222,3 +222,4 @@ for further change information.
libraries/Win32/Win32.cabal: Dependency of ``ghc`` library
libraries/xhtml/xhtml.cabal: Dependency of ``haddock`` executable
libraries/os-string/os-string.cabal: Dependency of ``filepath`` library
+ libraries/file-io/file-io.cabal: Dependency of ``directory`` library
=====================================
docs/users_guide/phases.rst
=====================================
@@ -1151,8 +1151,9 @@ for example).
:shortdesc: Control whether the RTS behaviour can be tweaked via command-line
flags and the ``GHCRTS`` environment variable. Using ``none``
means no RTS flags can be given; ``some`` means only a minimum
- of safe options can be given (the default); ``all`` (or no
- argument at all) means that all RTS flags are permitted; ``ignore``
+ of safe options can be given (the default, if ``-rtsopts`` is
+ not passed); ``all`` means that all RTS flags are permitted (the
+ default, if ``-rtsopts`` is passed with no argument); ``ignore``
means RTS flags can be given, but are treated as regular arguments and
passed to the Haskell program as arguments; ``ignoreAll`` is the same as
``ignore``, but ``GHCRTS`` is also ignored. ``-rtsopts`` does not
@@ -1161,11 +1162,12 @@ for example).
:type: dynamic
:category: linking
- :default: some
+ :default: ``some``, if ``-rtsopts`` is not passed; ``all``, if ``-rtsopts``
+ is passed with no argument.
This option affects the processing of RTS control options given
either on the command line or via the :envvar:`GHCRTS` environment
- variable. There are five possibilities:
+ variable. There are six possibilities:
``-rtsopts=none``
Disable all processing of RTS options. If ``+RTS`` appears
@@ -1181,18 +1183,22 @@ for example).
``GHCRTS`` options will be processed normally.
``-rtsopts=ignoreAll``
- Same as ``ignore`` but also ignores ``GHCRTS``.
+ Same as ``ignore`` with the exception of ``GHCRTS`` options, which are
+ also ignored.
``-rtsopts=some``
- [this is the default setting] Enable only the "safe" RTS
- options: (Currently only ``-?`` and ``--info``.) Any other RTS
- options on the command line or in the ``GHCRTS`` environment
- variable causes the program with to abort with an error message.
+ [this is the default setting, if ``-rtsopts`` is not passed] Enable only
+ the "safe" RTS options: (Currently only ``-?`` and ``--info``.) Any
+ other RTS options on the command line or in the ``GHCRTS`` environment
+ variable causes the program to abort with an error message.
- ``-rtsopts=all`` or just ``-rtsopts``
+ ``-rtsopts=all``
Enable *all* RTS option processing, both on the command line and
through the ``GHCRTS`` environment variable.
+ ``-rtsopts``
+ Equivalent to ``-rtsopts=all``.
+
In GHC 6.12.3 and earlier, the default was to process all RTS
options. However, since RTS options can be used to write logging
data to arbitrary files under the security context of the running
=====================================
hadrian/src/Packages.hs
=====================================
@@ -4,7 +4,7 @@ module Packages (
array, base, binary, bytestring, cabal, cabalSyntax, checkPpr,
checkExact, countDeps,
compareSizes, compiler, containers, deepseq, deriveConstants, directory, dumpDecls,
- exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform,
+ exceptions, filepath, fileio, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform,
ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim,
ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline,
hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy,
@@ -40,7 +40,7 @@ ghcPackages =
, ghcToolchain, ghcToolchainBin, haddockApi, haddockLibrary, haddock, haskeline, hsc2hs
, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, mtl, osString
, parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell
- , terminfo, text, time, transformers, unlit, unix, win32, xhtml
+ , terminfo, text, time, transformers, unlit, unix, win32, xhtml, fileio
, timeout
, lintersCommon
, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace ]
@@ -79,6 +79,7 @@ directory = lib "directory"
dumpDecls = util "dump-decls"
exceptions = lib "exceptions"
filepath = lib "filepath"
+fileio = lib "file-io"
genapply = util "genapply"
genprimopcode = util "genprimopcode"
ghc = prg "ghc-bin" `setPath` "ghc"
=====================================
hadrian/src/Rules/ToolArgs.hs
=====================================
@@ -138,6 +138,7 @@ toolTargets = [ cabalSyntax
, directory
, process
, filepath
+ , fileio
, osString
-- , ghc -- # depends on ghc library
-- , runGhc -- # depends on ghc library
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -83,8 +83,9 @@ stage0Packages = do
return $ [ cabalSyntax
, cabal
, compiler
- , directory -- depends on filepath
+ , directory -- depends on filepath, fileIo
, filepath -- depends on os-string
+ , fileio
, ghc
, ghcBoot
, ghcBootThNext
=====================================
libraries/directory
=====================================
@@ -1 +1 @@
-Subproject commit a97a8a8f30d652f972192122fd5f459a147c13e5
+Subproject commit 6045b93c4ef7a713c8f3d6837ca69f8e96b12bf1
=====================================
libraries/file-io
=====================================
@@ -0,0 +1 @@
+Subproject commit a4a0464ccd38e8380c202949a90b21d9e592aeef
=====================================
libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs
=====================================
@@ -438,13 +438,10 @@ instance Show IOException where
"" -> id
_ -> showString " (" . showString s . showString ")")
--- Note the use of "lazy". This means that
--- assert False (throw e)
--- will throw the assertion failure rather than e. See trac #5561.
assertError :: (?callStack :: CallStack) => Bool -> a -> a
assertError predicate v
- | predicate = lazy v
- | otherwise = unsafeDupablePerformIO $ do
+ | predicate = v
+ | otherwise = lazy $ unsafeDupablePerformIO $ do -- lazy: See Note [Strictness of assertError]
ccsStack <- currentCallStack
let
implicitParamCallStack = prettyCallStackLines ?callStack
@@ -452,6 +449,44 @@ assertError predicate v
stack = intercalate "\n" $ implicitParamCallStack ++ ccsCallStack
throwIO (AssertionFailed ("Assertion failed\n" ++ stack))
+{- Note [Strictness of assertError]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+It is vital that Demand Analysis does not see `assertError p e` as strict in e.
+#5561 details what happens otherwise, tested by libraries/base/tests/assert.hs:
+
+ let e1 i = throw Overflow
+ in assertError False (e1 5)
+
+This should *not* throw the Overflow exception; rather it should throw an
+AssertionError.
+Hence we use GHC.Exts.lazy to make assertError appear lazy in e, so that it
+is not called by-value.
+(Note that the reason we need `lazy` in the first place is that error has a
+bottoming result, which is strict in all free variables.)
+The way we achieve this is a bit subtle; before #24625 we defined it as
+
+ assertError p e | p = lazy e
+ | otherwise = error "assertion"
+
+but this means that in the following example (full code in T24625) we cannot
+cancel away the allocation of `Just x` because of the intervening `lazy`:
+
+ case assertError False (Just x) of Just y -> y
+ ==> { simplify }
+ case lazy (Just x) of Just y -> y
+
+Instead, we put `lazy` in the otherwise branch, thus
+
+ assertError p e | p = e
+ | otherwise = lazy $ error "assertion"
+
+The effect on #5561 is the same: since the otherwise branch appears lazy in e,
+the overall demand on `e` must be lazy as well.
+Furthermore, since there is no intervening `lazy` on the expected code path,
+the Simplifier may perform case-of-case on e and simplify the `Just x` example
+to `x`.
+-}
+
unsupportedOperation :: IOError
unsupportedOperation =
(IOError Nothing UnsupportedOperation ""
@@ -480,4 +515,3 @@ untangle coded message
_ -> (loc, "")
}
not_bar c = c /= '|'
-
=====================================
testsuite/tests/simplCore/should_compile/T24625.hs
=====================================
@@ -0,0 +1,14 @@
+module T24625 where
+
+import GHC.IO.Exception
+import GHC.Exts
+
+data Foo = Foo !Int !Int String
+
+true :: Bool
+true = True
+{-# NOINLINE true #-}
+
+function :: Int -> Int -> String -> Int
+function !a !b c = case assertError true (Foo a b c) of
+ Foo a b c -> a + b
=====================================
testsuite/tests/simplCore/should_compile/all.T
=====================================
@@ -526,5 +526,6 @@ test('T24808', [ grep_errmsg(r'myFunction') ], compile, ['-O -ddump-simpl'])
# T24944 needs -O2 because it's about SpecConstr
test('T24944', [extra_files(['T24944a.hs'])], multimod_compile, ['T24944', '-v0 -O2'])
+test('T24625', [ grep_errmsg(r'case lazy') ], compile, ['-O -fno-ignore-asserts -ddump-simpl -dsuppress-uniques'])
test('T24725a', [ grep_errmsg(r'testedRule')], compile, ['-O -ddump-rule-firings'])
test('T25033', normal, compile, ['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4fa319fa52b5f59125ff0a6d741c5a7e3c634e1...5418a03485eb7f656f328eb890edce79fb7c4e6e
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4fa319fa52b5f59125ff0a6d741c5a7e3c634e1...5418a03485eb7f656f328eb890edce79fb7c4e6e
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/20240819/e371abac/attachment-0001.html>
More information about the ghc-commits
mailing list