Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC
Commits:
-
bb21325d
by maralorn at 2025-06-11T18:27:05-04:00
-
7b5b7fac
by maralorn at 2025-06-11T18:27:05-04:00
-
e17445dd
by Andrew Lelechenko at 2025-06-11T18:27:06-04:00
21 changed files:
- libraries/base/changelog.md
- libraries/base/tests/IO/withBinaryFile002.stderr
- libraries/base/tests/IO/withFile002.stderr
- libraries/base/tests/IO/withFileBlocking002.stderr
- libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs
- libraries/ghc-internal/src/GHC/Internal/Exception/Type.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO.hs-boot
- libraries/ghc-internal/src/GHC/Internal/IO/Exception.hs-boot
- m4/fp_gcc_supports_no_pie.m4
- m4/fptools_set_c_ld_flags.m4
- testsuite/tests/deSugar/should_run/DsDoExprFailMsg.stderr
- testsuite/tests/deSugar/should_run/DsMonadCompFailMsg.stderr
- testsuite/tests/interface-stability/base-exports.stdout
- testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs
- testsuite/tests/interface-stability/base-exports.stdout-mingw32
- testsuite/tests/interface-stability/base-exports.stdout-ws-32
- testsuite/tests/th/T15321.stderr
- testsuite/tests/typecheck/should_compile/subsumption_sort_hole_fits.stderr
- testsuite/tests/typecheck/should_compile/valid_hole_fits.stderr
- utils/ghc-toolchain/src/GHC/Toolchain/Tools/Link.hs
- utils/haddock/hypsrc-test/ref/src/Quasiquoter.html
Changes:
... | ... | @@ -9,6 +9,7 @@ |
9 | 9 | * `Data.List.NonEmpty.{init,last,tails1}` are now defined using only total functions (rather than partial ones). ([CLC proposal #293](https://github.com/haskell/core-libraries-committee/issues/293))
|
10 | 10 | * `Data.List.NonEmpty` functions now have the same laziness as their `Data.List` counterparts (i.e. make them more strict than they currently are) ([CLC proposal #107](https://github.com/haskell/core-libraries-committee/issues/107))
|
11 | 11 | * `instance Functor NonEmpty` is now specified using `map` (rather than duplicating code). ([CLC proposal #300](https://github.com/haskell/core-libraries-committee/issues/300))
|
12 | + * `fail` from `MonadFail` now carries `HasCallStack` constraint. ([CLC proposal #327](https://github.com/haskell/core-libraries-committee/issues/327))
|
|
12 | 13 | * The `Data.Enum.enumerate` function was introduced ([CLC #306](https://github.com/haskell/core-libraries-committee/issues/306))
|
13 | 14 | * Worker threads used by various `base` facilities are now labelled with descriptive thread labels ([CLC proposal #305](https://github.com/haskell/core-libraries-committee/issues/305), [GHC #25452](https://gitlab.haskell.org/ghc/ghc/-/issues/25452)). Specifically, these include:
|
14 | 15 | * `Control.Concurrent.threadWaitRead`
|
1 | 1 | withBinaryFile002: Uncaught exception ghc-internal:GHC.Internal.IO.Exception.IOException:
|
2 | 2 | |
3 | 3 | user error (test)
|
4 | + |
|
5 | +HasCallStack backtrace:
|
|
6 | + throwIO, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:66:12 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
7 | + a type signature in an instance, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:65:13 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
8 | + fail, called at withBinaryFile002.hs:8:5 in main:Main
|
|
9 | + |
1 | 1 | withFile002: Uncaught exception ghc-internal:GHC.Internal.IO.Exception.IOException:
|
2 | 2 | |
3 | 3 | user error (test)
|
4 | + |
|
5 | +HasCallStack backtrace:
|
|
6 | + throwIO, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:66:12 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
7 | + a type signature in an instance, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:65:13 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
8 | + fail, called at withFile002.hs:8:5 in main:Main
|
|
9 | + |
1 | 1 | withFileBlocking002: Uncaught exception ghc-internal:GHC.Internal.IO.Exception.IOException:
|
2 | 2 | |
3 | 3 | user error (test)
|
4 | + |
|
5 | +HasCallStack backtrace:
|
|
6 | + throwIO, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:66:12 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
7 | + a type signature in an instance, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:65:13 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
8 | + fail, called at withFileBlocking002.hs:9:5 in main:Main
|
|
9 | + |
1 | +{-# LANGUAGE InstanceSigs #-}
|
|
1 | 2 | {-# LANGUAGE Trustworthy #-}
|
2 | 3 | {-# LANGUAGE NoImplicitPrelude #-}
|
3 | 4 | |
... | ... | @@ -13,7 +14,10 @@ |
13 | 14 | --
|
14 | 15 | module GHC.Internal.Control.Monad.Fail ( MonadFail(fail) ) where
|
15 | 16 | |
16 | -import GHC.Internal.Base (String, Monad(), Maybe(Nothing), IO(), failIO)
|
|
17 | +import GHC.Internal.Base (String, Monad(), Maybe(Nothing), IO(), (.))
|
|
18 | +import {-# SOURCE #-} GHC.Internal.IO (throwIO)
|
|
19 | +import {-# SOURCE #-} GHC.Internal.IO.Exception (userError)
|
|
20 | +import GHC.Internal.Stack.Types (HasCallStack)
|
|
17 | 21 | |
18 | 22 | -- | When a value is bound in @do@-notation, the pattern on the left
|
19 | 23 | -- hand side of @<-@ might not match. In this case, this class
|
... | ... | @@ -42,18 +46,21 @@ import GHC.Internal.Base (String, Monad(), Maybe(Nothing), IO(), failIO) |
42 | 46 | --
|
43 | 47 | -- @since base-4.9.0.0
|
44 | 48 | class Monad m => MonadFail m where
|
45 | - fail :: String -> m a
|
|
49 | + fail :: HasCallStack => String -> m a
|
|
46 | 50 | |
47 | 51 | |
48 | 52 | -- | @since base-4.9.0.0
|
49 | 53 | instance MonadFail Maybe where
|
54 | + fail :: HasCallStack => String -> Maybe a
|
|
50 | 55 | fail _ = Nothing
|
51 | 56 | |
52 | 57 | -- | @since base-4.9.0.0
|
53 | 58 | instance MonadFail [] where
|
54 | 59 | {-# INLINE fail #-}
|
60 | + fail :: HasCallStack => String -> [a]
|
|
55 | 61 | fail _ = []
|
56 | 62 | |
57 | 63 | -- | @since base-4.9.0.0
|
58 | 64 | instance MonadFail IO where
|
59 | - fail = failIO |
|
65 | + fail :: HasCallStack => String -> IO a
|
|
66 | + fail = throwIO . userError |
... | ... | @@ -2,7 +2,8 @@ |
2 | 2 | {-# LANGUAGE NoImplicitPrelude #-}
|
3 | 3 | |
4 | 4 | module GHC.Internal.Exception.Type
|
5 | - ( SomeException
|
|
5 | + ( Exception
|
|
6 | + , SomeException
|
|
6 | 7 | , divZeroException
|
7 | 8 | , overflowException
|
8 | 9 | , ratioZeroDenomException
|
... | ... | @@ -12,6 +13,8 @@ module GHC.Internal.Exception.Type |
12 | 13 | -- See W1 of Note [Tracking dependencies on primitives] in GHC.Internal.Base
|
13 | 14 | import GHC.Internal.Types ()
|
14 | 15 | |
16 | +class Exception e
|
|
17 | + |
|
15 | 18 | data SomeException
|
16 | 19 | divZeroException, overflowException,
|
17 | 20 | ratioZeroDenomException, underflowException :: SomeException |
... | ... | @@ -3,8 +3,10 @@ |
3 | 3 | |
4 | 4 | module GHC.Internal.IO where
|
5 | 5 | |
6 | +import GHC.Internal.Stack.Types (HasCallStack)
|
|
6 | 7 | import GHC.Internal.Types
|
7 | -import {-# SOURCE #-} GHC.Internal.Exception.Type (SomeException)
|
|
8 | +import {-# SOURCE #-} GHC.Internal.Exception.Type (Exception, SomeException)
|
|
8 | 9 | |
9 | 10 | mplusIO :: IO a -> IO a -> IO a
|
10 | 11 | mkUserError :: [Char] -> SomeException
|
12 | +throwIO :: (HasCallStack, Exception e) => e -> IO a |
... | ... | @@ -4,7 +4,7 @@ |
4 | 4 | module GHC.Internal.IO.Exception where
|
5 | 5 | |
6 | 6 | import GHC.Internal.Base
|
7 | -import GHC.Internal.Exception
|
|
7 | +import {-# SOURCE #-} GHC.Internal.Exception.Type
|
|
8 | 8 | |
9 | 9 | data IOException
|
10 | 10 | instance Exception IOException
|
... | ... | @@ -7,9 +7,9 @@ AC_DEFUN([FP_GCC_SUPPORTS_NO_PIE], |
7 | 7 | AC_REQUIRE([AC_PROG_CC])
|
8 | 8 | AC_MSG_CHECKING([whether CC supports -no-pie])
|
9 | 9 | echo 'int main() { return 0; }' > conftest.c
|
10 | - "$CC" $CONF_GCC_CC_OPTS_STAGE2 -c conftest.c
|
|
10 | + "$CC" -c conftest.c
|
|
11 | 11 | # Some GCC versions only warn when passed an unrecognized flag.
|
12 | - if "$CC" $CONF_GCC_LINKER_OPTS_STAGE2 -no-pie -Werror conftest.o -o conftest > conftest.txt 2>&1 && ! grep -i unrecognized conftest.txt > /dev/null 2>&1; then
|
|
12 | + if "$CC" -no-pie -Werror conftest.o -o conftest > conftest.txt 2>&1 && ! grep -i unrecognized conftest.txt > /dev/null 2>&1; then
|
|
13 | 13 | CONF_GCC_SUPPORTS_NO_PIE=YES
|
14 | 14 | AC_MSG_RESULT([yes])
|
15 | 15 | else
|
... | ... | @@ -109,6 +109,9 @@ AC_DEFUN([FPTOOLS_SET_C_LD_FLAGS], |
109 | 109 | $2="$$2 -mcmodel=medium"
|
110 | 110 | ;;
|
111 | 111 | |
112 | + javascript*)
|
|
113 | + $3="$$3 -sEXPORTED_RUNTIME_METHODS=HEAP8,HEAPU8"
|
|
114 | + |
|
112 | 115 | esac
|
113 | 116 | |
114 | 117 | AC_MSG_RESULT([done])
|
1 | 1 | DsDoExprFailMsg: Uncaught exception ghc-internal:GHC.Internal.IO.Exception.IOException:
|
2 | 2 | |
3 | 3 | user error (Pattern match failure in 'do' block at DsDoExprFailMsg.hs:2:3-8)
|
4 | + |
|
5 | +HasCallStack backtrace:
|
|
6 | + throwIO, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:66:12 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
7 | + a type signature in an instance, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:65:13 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
8 | + a do statement, called at DsDoExprFailMsg.hs:2:3 in main:Main
|
|
9 | + |
1 | 1 | DsMonadCompFailMsg: Uncaught exception ghc-internal:GHC.Internal.IO.Exception.IOException:
|
2 | 2 | |
3 | 3 | user error (Pattern match failure in monad comprehension at DsMonadCompFailMsg.hs:2:14-19)
|
4 | + |
|
5 | +HasCallStack backtrace:
|
|
6 | + throwIO, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:66:12 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
7 | + a type signature in an instance, called at libraries/ghc-internal/src/GHC/Internal/Control/Monad/Fail.hs:65:13 in ghc-internal:GHC.Internal.Control.Monad.Fail
|
|
8 | + a monad comprehension pattern, called at DsMonadCompFailMsg.hs:2:14 in main:Main
|
|
9 | + |
... | ... | @@ -452,7 +452,7 @@ module Control.Monad where |
452 | 452 | {-# MINIMAL (>>=) #-}
|
453 | 453 | type MonadFail :: (* -> *) -> Constraint
|
454 | 454 | class Monad m => MonadFail m where
|
455 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
455 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
456 | 456 | {-# MINIMAL fail #-}
|
457 | 457 | type MonadPlus :: (* -> *) -> Constraint
|
458 | 458 | class (GHC.Internal.Base.Alternative m, Monad m) => MonadPlus m where
|
... | ... | @@ -492,7 +492,7 @@ module Control.Monad.Fail where |
492 | 492 | -- Safety: Safe
|
493 | 493 | type MonadFail :: (* -> *) -> Constraint
|
494 | 494 | class GHC.Internal.Base.Monad m => MonadFail m where
|
495 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
495 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
496 | 496 | {-# MINIMAL fail #-}
|
497 | 497 | |
498 | 498 | module Control.Monad.Fix where
|
... | ... | @@ -9991,7 +9991,7 @@ module Prelude where |
9991 | 9991 | {-# MINIMAL (>>=) #-}
|
9992 | 9992 | type MonadFail :: (* -> *) -> Constraint
|
9993 | 9993 | class Monad m => MonadFail m where
|
9994 | - fail :: forall a. String -> m a
|
|
9994 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => String -> m a
|
|
9995 | 9995 | {-# MINIMAL fail #-}
|
9996 | 9996 | type Monoid :: * -> Constraint
|
9997 | 9997 | class Semigroup a => Monoid a where
|
... | ... | @@ -452,7 +452,7 @@ module Control.Monad where |
452 | 452 | {-# MINIMAL (>>=) #-}
|
453 | 453 | type MonadFail :: (* -> *) -> Constraint
|
454 | 454 | class Monad m => MonadFail m where
|
455 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
455 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
456 | 456 | {-# MINIMAL fail #-}
|
457 | 457 | type MonadPlus :: (* -> *) -> Constraint
|
458 | 458 | class (GHC.Internal.Base.Alternative m, Monad m) => MonadPlus m where
|
... | ... | @@ -492,7 +492,7 @@ module Control.Monad.Fail where |
492 | 492 | -- Safety: Safe
|
493 | 493 | type MonadFail :: (* -> *) -> Constraint
|
494 | 494 | class GHC.Internal.Base.Monad m => MonadFail m where
|
495 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
495 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
496 | 496 | {-# MINIMAL fail #-}
|
497 | 497 | |
498 | 498 | module Control.Monad.Fix where
|
... | ... | @@ -13037,7 +13037,7 @@ module Prelude where |
13037 | 13037 | {-# MINIMAL (>>=) #-}
|
13038 | 13038 | type MonadFail :: (* -> *) -> Constraint
|
13039 | 13039 | class Monad m => MonadFail m where
|
13040 | - fail :: forall a. String -> m a
|
|
13040 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => String -> m a
|
|
13041 | 13041 | {-# MINIMAL fail #-}
|
13042 | 13042 | type Monoid :: * -> Constraint
|
13043 | 13043 | class Semigroup a => Monoid a where
|
... | ... | @@ -452,7 +452,7 @@ module Control.Monad where |
452 | 452 | {-# MINIMAL (>>=) #-}
|
453 | 453 | type MonadFail :: (* -> *) -> Constraint
|
454 | 454 | class Monad m => MonadFail m where
|
455 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
455 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
456 | 456 | {-# MINIMAL fail #-}
|
457 | 457 | type MonadPlus :: (* -> *) -> Constraint
|
458 | 458 | class (GHC.Internal.Base.Alternative m, Monad m) => MonadPlus m where
|
... | ... | @@ -492,7 +492,7 @@ module Control.Monad.Fail where |
492 | 492 | -- Safety: Safe
|
493 | 493 | type MonadFail :: (* -> *) -> Constraint
|
494 | 494 | class GHC.Internal.Base.Monad m => MonadFail m where
|
495 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
495 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
496 | 496 | {-# MINIMAL fail #-}
|
497 | 497 | |
498 | 498 | module Control.Monad.Fix where
|
... | ... | @@ -10271,7 +10271,7 @@ module Prelude where |
10271 | 10271 | {-# MINIMAL (>>=) #-}
|
10272 | 10272 | type MonadFail :: (* -> *) -> Constraint
|
10273 | 10273 | class Monad m => MonadFail m where
|
10274 | - fail :: forall a. String -> m a
|
|
10274 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => String -> m a
|
|
10275 | 10275 | {-# MINIMAL fail #-}
|
10276 | 10276 | type Monoid :: * -> Constraint
|
10277 | 10277 | class Semigroup a => Monoid a where
|
... | ... | @@ -452,7 +452,7 @@ module Control.Monad where |
452 | 452 | {-# MINIMAL (>>=) #-}
|
453 | 453 | type MonadFail :: (* -> *) -> Constraint
|
454 | 454 | class Monad m => MonadFail m where
|
455 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
455 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
456 | 456 | {-# MINIMAL fail #-}
|
457 | 457 | type MonadPlus :: (* -> *) -> Constraint
|
458 | 458 | class (GHC.Internal.Base.Alternative m, Monad m) => MonadPlus m where
|
... | ... | @@ -492,7 +492,7 @@ module Control.Monad.Fail where |
492 | 492 | -- Safety: Safe
|
493 | 493 | type MonadFail :: (* -> *) -> Constraint
|
494 | 494 | class GHC.Internal.Base.Monad m => MonadFail m where
|
495 | - fail :: forall a. GHC.Internal.Base.String -> m a
|
|
495 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => GHC.Internal.Base.String -> m a
|
|
496 | 496 | {-# MINIMAL fail #-}
|
497 | 497 | |
498 | 498 | module Control.Monad.Fix where
|
... | ... | @@ -9991,7 +9991,7 @@ module Prelude where |
9991 | 9991 | {-# MINIMAL (>>=) #-}
|
9992 | 9992 | type MonadFail :: (* -> *) -> Constraint
|
9993 | 9993 | class Monad m => MonadFail m where
|
9994 | - fail :: forall a. String -> m a
|
|
9994 | + fail :: forall a. GHC.Internal.Stack.Types.HasCallStack => String -> m a
|
|
9995 | 9995 | {-# MINIMAL fail #-}
|
9996 | 9996 | type Monoid :: * -> Constraint
|
9997 | 9997 | class Semigroup a => Monoid a where
|
... | ... | @@ -3,7 +3,9 @@ T15321.hs:9:9: error: [GHC-88464] |
3 | 3 | • In the expression: _ "baz"
|
4 | 4 | In the untyped splice: $(_ "baz")
|
5 | 5 | • Valid hole fits include
|
6 | - fail :: forall (m :: * -> *) a. MonadFail m => String -> m a
|
|
6 | + fail :: forall (m :: * -> *) a.
|
|
7 | + (MonadFail m, GHC.Internal.Stack.Types.HasCallStack) =>
|
|
8 | + String -> m a
|
|
7 | 9 | with fail @GHC.Internal.TH.Syntax.Q @GHC.Internal.TH.Syntax.Exp
|
8 | 10 | (imported from ‘Prelude’ at T15321.hs:3:8-13
|
9 | 11 | (and originally defined in ‘GHC.Internal.Control.Monad.Fail’))
|
1 | - |
|
2 | 1 | subsumption_sort_hole_fits.hs:2:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)]
|
3 | 2 | • Found hole: _ :: String -> [String]
|
4 | 3 | • In the expression: _ "hello, world"
|
... | ... | @@ -24,7 +23,9 @@ subsumption_sort_hole_fits.hs:2:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdef |
24 | 23 | with mempty @(String -> [String])
|
25 | 24 | (imported from ‘Prelude’ at subsumption_sort_hole_fits.hs:1:1
|
26 | 25 | (and originally defined in ‘GHC.Internal.Base’))
|
27 | - fail :: forall (m :: * -> *) a. MonadFail m => String -> m a
|
|
26 | + fail :: forall (m :: * -> *) a.
|
|
27 | + (MonadFail m, GHC.Internal.Stack.Types.HasCallStack) =>
|
|
28 | + String -> m a
|
|
28 | 29 | with fail @[] @String
|
29 | 30 | (imported from ‘Prelude’ at subsumption_sort_hole_fits.hs:1:1
|
30 | 31 | (and originally defined in ‘GHC.Internal.Control.Monad.Fail’))
|
... | ... | @@ -36,3 +37,4 @@ subsumption_sort_hole_fits.hs:2:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdef |
36 | 37 | with pure @[] @String
|
37 | 38 | (imported from ‘Prelude’ at subsumption_sort_hole_fits.hs:1:1
|
38 | 39 | (and originally defined in ‘GHC.Internal.Base’))
|
40 | + |
... | ... | @@ -247,7 +247,9 @@ valid_hole_fits.hs:41:8: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] |
247 | 247 | with print @String
|
248 | 248 | (imported from ‘Prelude’ at valid_hole_fits.hs:3:1-40
|
249 | 249 | (and originally defined in ‘GHC.Internal.System.IO’))
|
250 | - fail :: forall (m :: * -> *) a. MonadFail m => String -> m a
|
|
250 | + fail :: forall (m :: * -> *) a.
|
|
251 | + (MonadFail m, GHC.Internal.Stack.Types.HasCallStack) =>
|
|
252 | + String -> m a
|
|
251 | 253 | with fail @IO @()
|
252 | 254 | (imported from ‘Prelude’ at valid_hole_fits.hs:3:1-40
|
253 | 255 | (and originally defined in ‘GHC.Internal.Control.Monad.Fail’))
|
... | ... | @@ -324,6 +324,10 @@ addPlatformDepLinkFlags archOs cc ccLink0 = do |
324 | 324 | ArchOS ArchPPC OSAIX ->
|
325 | 325 | -- We need `-D_THREAD_SAFE` to unlock the thread-local `errno`.
|
326 | 326 | return $ ccLink2 & over _prgFlags (++["-D_THREAD_SAFE","-Wl,-bnotextro"])
|
327 | + ArchOS ArchJavaScript OSGhcjs ->
|
|
328 | + -- Since https://github.com/emscripten-core/emscripten/blob/main/ChangeLog.md#407---041525
|
|
329 | + -- the emcc linker does not export the HEAP8 memory view which is used by the js RTS by default anymore.
|
|
330 | + return $ ccLink2 & _prgFlags %++ "-sEXPORTED_RUNTIME_METHODS=HEAP8,HEAPU8"
|
|
327 | 331 | _ ->
|
328 | 332 | return ccLink2
|
329 | 333 |
... | ... | @@ -405,8 +405,10 @@ forall a. String -> Q a |
405 | 405 | ><span class="annot"
|
406 | 406 | ><span class="annottext"
|
407 | 407 | >String -> Q a
|
408 | -forall a. String -> Q a
|
|
409 | -forall (m :: * -> *) a. MonadFail m => String -> m a
|
|
408 | +forall a. HasCallStack => String -> Q a
|
|
409 | +forall (m :: * -> *) a.
|
|
410 | +(MonadFail m, HasCallStack) =>
|
|
411 | +String -> m a
|
|
410 | 412 | </span
|
411 | 413 | ><span class="hs-identifier hs-var"
|
412 | 414 | >fail</span
|