[Git][ghc/ghc][wip/absolute-i-paths] 8 commits: Expect T4267 to pass
Ben Gamari
gitlab at gitlab.haskell.org
Tue Mar 31 16:32:51 UTC 2020
Ben Gamari pushed to branch wip/absolute-i-paths at Glasgow Haskell Compiler / GHC
Commits:
f024b6e3 by Sylvain Henry at 2020-03-30T12:48:39+02:00
Expect T4267 to pass
Since 54250f2d8de910b094070c1b48f086030df634b1 we expected T4267 to
fail, but it passes on CI.
- - - - -
57b888c0 by Ryan Scott at 2020-03-31T10:54:20-04:00
Require GHC 8.8 as the minimum compiler for bootstrapping
This allows us to remove several bits of CPP that are either always
true or no longer reachable. As an added bonus, we no longer need to
worry about importing `Control.Monad.Fail.fail` qualified to avoid
clashing with `Control.Monad.fail`, since the latter is now the same
as the former.
- - - - -
33f09551 by Ryan Scott at 2020-03-31T10:54:57-04:00
Add regression test for #17963
The panic in #17963 happened to be fixed by commit
e3c374cc5bd7eb49649b9f507f9f7740697e3f70. This patch adds a
regression test to ensure that it remains fixed.
Fixes #17963.
- - - - -
09a36e80 by Ömer Sinan Ağacan at 2020-03-31T10:55:37-04:00
Simplify stderrSupportsAnsiColors
The combinator andM is used only once, and the code is shorter and
simpler if you inline it.
- - - - -
95bccdd0 by Ben Gamari at 2020-03-31T10:56:19-04:00
base: Ensure that encoding global variables aren't inlined
As noted in #17970, these (e.g. `getFileSystemEncoding` and
`setFileSystemEncoding`) previously had unfoldings, which would
break their global-ness.
While not strictly necessary, I also add a NOINLINE on
`initLocaleEncoding` since it is used in `System.IO`, ensuring that we
only system's query the locale encoding once.
Fixes #17970.
- - - - -
982aaa83 by Andreas Klebinger at 2020-03-31T10:56:55-04:00
Update hadrian index revision.
Required in order to build hadrian using ghc-8.10
- - - - -
4b9c5864 by Ben Gamari at 2020-03-31T10:57:32-04:00
integer-gmp: Bump version and add changelog entry
- - - - -
de7bfdb1 by Matthew Pickering at 2020-03-31T12:32:45-04:00
Hadrian: Make -i paths absolute
The primary reason for this change is that ghcide does not work with
relative paths. It also matches what cabal and stack do, they always
pass absolute paths.
- - - - -
30 changed files:
- .gitlab-ci.yml
- compiler/GHC/Core/Lint.hs
- compiler/GHC/Core/Make.hs
- compiler/GHC/Core/Op/ConstantFold.hs
- compiler/GHC/Core/Op/Specialise.hs
- compiler/GHC/Core/Unify.hs
- compiler/GHC/Types/Unique/Supply.hs
- compiler/main/SysTools/Process.hs
- compiler/main/SysTools/Terminal.hs
- compiler/typecheck/TcRnTypes.hs
- compiler/typecheck/TcSMonad.hs
- compiler/utils/Binary.hs
- compiler/utils/IOEnv.hs
- configure.ac
- hadrian/cabal.project
- hadrian/src/Hadrian/Utilities.hs
- hadrian/src/Settings/Builders/Cabal.hs
- hadrian/src/Settings/Builders/Ghc.hs
- libraries/base/Control/Monad/ST/Lazy/Imp.hs
- libraries/base/GHC/IO/Encoding.hs
- libraries/base/GHC/ST.hs
- libraries/base/Text/ParserCombinators/ReadPrec.hs
- libraries/ghci/GHCi/TH.hs
- libraries/integer-gmp/changelog.md
- libraries/integer-gmp/integer-gmp.cabal
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- testsuite/tests/perf/should_run/all.T
- + testsuite/tests/polykinds/T17963.hs
- + testsuite/tests/polykinds/T17963.stderr
- testsuite/tests/polykinds/all.T
Changes:
=====================================
.gitlab-ci.yml
=====================================
@@ -2,7 +2,7 @@ variables:
GIT_SSL_NO_VERIFY: "1"
# Commit of ghc/ci-images repository from which to pull Docker images
- DOCKER_REV: 408eff66aef6ca2b44446c694c5a56d6ca0460cc
+ DOCKER_REV: 3f731f5d37a156e7ebe10cd32656946083baaf4a
# Sequential version number capturing the versions of all tools fetched by
# .gitlab/ci.sh.
@@ -390,7 +390,7 @@ validate-x86_64-darwin:
tags:
- x86_64-darwin
variables:
- GHC_VERSION: 8.6.5
+ GHC_VERSION: 8.8.3
CABAL_INSTALL_VERSION: 3.0.0.0
BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-apple-darwin.tar.xz"
MACOSX_DEPLOYMENT_TARGET: "10.7"
@@ -419,7 +419,7 @@ validate-x86_64-darwin:
tags:
- x86_64-darwin
variables:
- GHC_VERSION: 8.6.3
+ GHC_VERSION: 8.8.3
MACOSX_DEPLOYMENT_TARGET: "10.7"
ac_cv_func_clock_gettime: "no"
LANG: "en_US.UTF-8"
=====================================
compiler/GHC/Core/Lint.hs
=====================================
@@ -70,7 +70,6 @@ import GHC.Types.Demand ( splitStrictSig, isBotDiv )
import GHC.Driver.Types
import GHC.Driver.Session
import Control.Monad
-import qualified Control.Monad.Fail as MonadFail
import MonadUtils
import Data.Foldable ( toList )
import Data.List.NonEmpty ( NonEmpty )
@@ -2249,16 +2248,13 @@ instance Applicative LintM where
(<*>) = ap
instance Monad LintM where
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
m >>= k = LintM (\ env errs ->
let (res, errs') = unLintM m env errs in
case res of
Just r -> unLintM (k r) env errs'
Nothing -> (Nothing, errs'))
-instance MonadFail.MonadFail LintM where
+instance MonadFail LintM where
fail err = failWithL (text err)
instance HasDynFlags LintM where
=====================================
compiler/GHC/Core/Make.hs
=====================================
@@ -85,7 +85,6 @@ import Util
import Data.List
import Data.Char ( ord )
-import Control.Monad.Fail as MonadFail ( MonadFail )
infixl 4 `mkCoreApp`, `mkCoreApps`
@@ -640,7 +639,7 @@ mkFoldrExpr elt_ty result_ty c n list = do
`App` list)
-- | Make a 'build' expression applied to a locally-bound worker function
-mkBuildExpr :: (MonadFail.MonadFail m, MonadThings m, MonadUnique m)
+mkBuildExpr :: (MonadFail m, MonadThings m, MonadUnique m)
=> Type -- ^ Type of list elements to be built
-> ((Id, Type) -> (Id, Type) -> m CoreExpr) -- ^ Function that, given information about the 'Id's
-- of the binders for the build worker function, returns
=====================================
compiler/GHC/Core/Op/ConstantFold.hs
=====================================
@@ -61,7 +61,6 @@ import GHC.Core.Coercion (mkUnbranchedAxInstCo,mkSymCo,Role(..))
import Control.Applicative ( Alternative(..) )
import Control.Monad
-import qualified Control.Monad.Fail as MonadFail
import Data.Bits as Bits
import qualified Data.ByteString as BS
import Data.Int
@@ -796,11 +795,7 @@ instance Monad RuleM where
Nothing -> Nothing
Just r -> runRuleM (g r) env iu fn args
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
-
-instance MonadFail.MonadFail RuleM where
+instance MonadFail RuleM where
fail _ = mzero
instance Alternative RuleM where
=====================================
compiler/GHC/Core/Op/Specialise.hs
=====================================
@@ -50,7 +50,6 @@ import GHC.Types.Unique.DFM
import GHC.Core.TyCo.Rep (TyCoBinder (..))
import Control.Monad
-import qualified Control.Monad.Fail as MonadFail
{-
************************************************************************
@@ -2551,11 +2550,8 @@ instance Monad SpecM where
case f y of
SpecM z ->
z
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
-instance MonadFail.MonadFail SpecM where
+instance MonadFail SpecM where
fail str = SpecM $ error str
instance MonadUnique SpecM where
=====================================
compiler/GHC/Core/Unify.hs
=====================================
@@ -46,7 +46,6 @@ import GHC.Types.Unique.FM
import GHC.Types.Unique.Set
import Control.Monad
-import qualified Control.Monad.Fail as MonadFail
import Control.Applicative hiding ( empty )
import qualified Control.Applicative
@@ -1244,9 +1243,6 @@ instance Applicative UM where
(<*>) = ap
instance Monad UM where
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
m >>= k = UM (\state ->
do { (state', v) <- unUM m state
; unUM (k v) state' })
@@ -1260,7 +1256,7 @@ instance Alternative UM where
instance MonadPlus UM
-instance MonadFail.MonadFail UM where
+instance MonadFail UM where
fail _ = UM (\_ -> SurelyApart) -- failed pattern match
initUM :: TvSubstEnv -- subst to extend
=====================================
compiler/GHC/Types/Unique/Supply.hs
=====================================
@@ -44,7 +44,6 @@ import MonadUtils
import Control.Monad
import Data.Bits
import Data.Char
-import Control.Monad.Fail as Fail
#include "Unique.h"
@@ -156,7 +155,7 @@ instance Applicative UniqSM where
(*>) = thenUs_
-- TODO: try to get rid of this instance
-instance Fail.MonadFail UniqSM where
+instance MonadFail UniqSM where
fail = panic
-- | Run the 'UniqSM' action, returning the final 'UniqSupply'
=====================================
compiler/main/SysTools/Process.hs
=====================================
@@ -36,14 +36,10 @@ import FileCleanup
-- @process >= 1.6.8.0@).
enableProcessJobs :: CreateProcess -> CreateProcess
#if defined(MIN_VERSION_process)
-#if MIN_VERSION_process(1,6,8)
enableProcessJobs opts = opts { use_process_jobs = True }
#else
enableProcessJobs opts = opts
#endif
-#else
-enableProcessJobs opts = opts
-#endif
-- Similar to System.Process.readCreateProcessWithExitCode, but stderr is
-- inherited from the parent process, and output to stderr is not captured.
=====================================
compiler/main/SysTools/Terminal.hs
=====================================
@@ -32,20 +32,13 @@ import qualified System.Win32 as Win32
stderrSupportsAnsiColors :: IO Bool
stderrSupportsAnsiColors = do
#if defined(MIN_VERSION_terminfo)
- queryTerminal stdError `andM` do
- (termSupportsColors <$> setupTermFromEnv)
- `catch` \ (_ :: SetupTermError) ->
- pure False
-
+ stderr_available <- queryTerminal stdError
+ if stderr_available then
+ fmap termSupportsColors setupTermFromEnv
+ `catch` \ (_ :: SetupTermError) -> pure False
+ else
+ pure False
where
-
- andM :: Monad m => m Bool -> m Bool -> m Bool
- andM mx my = do
- x <- mx
- if x
- then my
- else pure x
-
termSupportsColors :: Terminal -> Bool
termSupportsColors term = fromMaybe 0 (getCapability term termColors) > 0
=====================================
compiler/typecheck/TcRnTypes.hs
=====================================
@@ -124,7 +124,6 @@ import PrelNames ( isUnboundName )
import GHC.Types.CostCentre.State
import Control.Monad (ap)
-import qualified Control.Monad.Fail as MonadFail
import Data.Set ( Set )
import qualified Data.Set as S
@@ -1653,14 +1652,11 @@ instance Applicative TcPluginM where
(<*>) = ap
instance Monad TcPluginM where
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
TcPluginM m >>= k =
TcPluginM (\ ev -> do a <- m ev
runTcPluginM (k a) ev)
-instance MonadFail.MonadFail TcPluginM where
+instance MonadFail TcPluginM where
fail x = TcPluginM (const $ fail x)
runTcPluginM :: TcPluginM a -> EvBindsVar -> TcM a
=====================================
compiler/typecheck/TcSMonad.hs
=====================================
@@ -177,7 +177,6 @@ import Maybes
import GHC.Core.Map
import Control.Monad
-import qualified Control.Monad.Fail as MonadFail
import MonadUtils
import Data.IORef
import Data.List ( partition, mapAccumL )
@@ -2699,12 +2698,9 @@ instance Applicative TcS where
(<*>) = ap
instance Monad TcS where
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
m >>= k = TcS (\ebs -> unTcS m ebs >>= \r -> unTcS (k r) ebs)
-instance MonadFail.MonadFail TcS where
+instance MonadFail TcS where
fail err = TcS (\_ -> fail err)
instance MonadUnique TcS where
=====================================
compiler/utils/Binary.hs
=====================================
@@ -829,12 +829,10 @@ instance Binary RuntimeRep where
put_ bh AddrRep = putByte bh 9
put_ bh FloatRep = putByte bh 10
put_ bh DoubleRep = putByte bh 11
-#if __GLASGOW_HASKELL__ >= 807
put_ bh Int8Rep = putByte bh 12
put_ bh Word8Rep = putByte bh 13
put_ bh Int16Rep = putByte bh 14
put_ bh Word16Rep = putByte bh 15
-#endif
#if __GLASGOW_HASKELL__ >= 809
put_ bh Int32Rep = putByte bh 16
put_ bh Word32Rep = putByte bh 17
@@ -855,12 +853,10 @@ instance Binary RuntimeRep where
9 -> pure AddrRep
10 -> pure FloatRep
11 -> pure DoubleRep
-#if __GLASGOW_HASKELL__ >= 807
12 -> pure Int8Rep
13 -> pure Word8Rep
14 -> pure Int16Rep
15 -> pure Word16Rep
-#endif
#if __GLASGOW_HASKELL__ >= 809
16 -> pure Int32Rep
17 -> pure Word32Rep
=====================================
compiler/utils/IOEnv.hs
=====================================
@@ -43,7 +43,6 @@ import Data.IORef ( IORef, newIORef, readIORef, writeIORef, modifyIORef,
import System.IO.Unsafe ( unsafeInterleaveIO )
import System.IO ( fixIO )
import Control.Monad
-import qualified Control.Monad.Fail as MonadFail
import MonadUtils
import Control.Applicative (Alternative(..))
@@ -60,11 +59,8 @@ unIOEnv (IOEnv m) = m
instance Monad (IOEnv m) where
(>>=) = thenM
(>>) = (*>)
-#if !MIN_VERSION_base(4,13,0)
- fail = MonadFail.fail
-#endif
-instance MonadFail.MonadFail (IOEnv m) where
+instance MonadFail (IOEnv m) where
fail _ = failM -- Ignore the string
instance Applicative (IOEnv m) where
=====================================
configure.ac
=====================================
@@ -158,8 +158,8 @@ if test "$WithGhc" = ""
then
AC_MSG_ERROR([GHC is required.])
fi
-FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[8.6],
- [AC_MSG_ERROR([GHC version 8.6 or later is required to compile GHC.])])
+FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[8.8],
+ [AC_MSG_ERROR([GHC version 8.8 or later is required to compile GHC.])])
if test `expr $GhcMinVersion % 2` = "1"
then
=====================================
hadrian/cabal.project
=====================================
@@ -1,7 +1,7 @@
packages: ./
-- This essentially freezes the build plan for hadrian
-index-state: 2019-12-16T07:24:23Z
+index-state: 2020-03-28T07:24:23Z
-- N.B. Compile with -O0 since this is not a performance-critical executable
-- and the Cabal takes nearly twice as long to build with -O1. See #16817.
=====================================
hadrian/src/Hadrian/Utilities.hs
=====================================
@@ -40,7 +40,6 @@ import Data.Char
import Data.Dynamic (Dynamic, fromDynamic, toDyn)
import Data.Functor
import Data.HashMap.Strict (HashMap)
-import Data.List (isPrefixOf)
import Data.List.Extra
import Data.Maybe
import Data.Typeable (TypeRep, typeOf)
=====================================
hadrian/src/Settings/Builders/Cabal.hs
=====================================
@@ -1,6 +1,5 @@
module Settings.Builders.Cabal (cabalBuilderArgs) where
-import Hadrian.Builder (getBuilderPath, needBuilder)
import Hadrian.Haskell.Cabal
import Builder
=====================================
hadrian/src/Settings/Builders/Ghc.hs
=====================================
@@ -2,8 +2,6 @@
module Settings.Builders.Ghc (ghcBuilderArgs, haddockGhcArgs) where
-import Data.List.Extra (splitOn)
-
import Hadrian.Haskell.Cabal
import Hadrian.Haskell.Cabal.Type
@@ -13,6 +11,7 @@ import Settings.Builders.Common
import Settings.Warnings
import qualified Context as Context
import Rules.Libffi (libffiName)
+import System.Directory
ghcBuilderArgs :: Args
ghcBuilderArgs = mconcat [ compileAndLinkHs, compileC, findHsDependencies
@@ -214,18 +213,20 @@ packageGhcArgs = do
includeGhcArgs :: Args
includeGhcArgs = do
pkg <- getPackage
- path <- getBuildPath
+ path <- exprIO . makeAbsolute =<< getBuildPath
context <- getContext
srcDirs <- getContextData srcDirs
- autogen <- expr $ autogenPath context
+ abSrcDirs <- exprIO $ mapM makeAbsolute [ (pkgPath pkg -/- dir) | dir <- srcDirs ]
+ autogen <- expr (autogenPath context)
+ cautogen <- exprIO (makeAbsolute autogen)
stage <- getStage
- libPath <- expr $ stageLibPath stage
+ libPath <- expr (stageLibPath stage)
let cabalMacros = autogen -/- "cabal_macros.h"
expr $ need [cabalMacros]
mconcat [ arg "-i"
, arg $ "-i" ++ path
- , arg $ "-i" ++ autogen
- , pure [ "-i" ++ pkgPath pkg -/- dir | dir <- srcDirs ]
+ , arg $ "-i" ++ cautogen
+ , pure [ "-i" ++ d | d <- abSrcDirs ]
, cIncludeArgs
, arg $ "-I" ++ libPath
, arg $ "-optc-I" ++ libPath
=====================================
libraries/base/Control/Monad/ST/Lazy/Imp.hs
=====================================
@@ -8,7 +8,7 @@
-- Module : Control.Monad.ST.Lazy.Imp
-- Copyright : (c) The University of Glasgow 2001
-- License : BSD-style (see the file libraries/base/LICENSE)
---
+--
-- Maintainer : libraries at haskell.org
-- Stability : provisional
-- Portability : non-portable (requires universal quantification for runST)
@@ -44,7 +44,6 @@ import qualified Control.Monad.ST.Unsafe as ST
import qualified GHC.ST as GHC.ST
import GHC.Base
-import qualified Control.Monad.Fail as Fail
-- | The lazy @'ST' monad.
-- The ST monad allows for destructive updates, but is escapable (unlike IO).
@@ -192,7 +191,7 @@ instance Monad (ST s) where
unST (k r) new_s
-- | @since 4.10
-instance Fail.MonadFail (ST s) where
+instance MonadFail (ST s) where
fail s = errorWithoutStackTrace s
-- | Return the value computed by an 'ST' computation.
@@ -205,8 +204,8 @@ runST (ST st) = runRW# (\s -> case st (S# s) of (r, _) -> r)
-- inside the computation.
-- Note that if @f@ is strict, @'fixST' f = _|_ at .
fixST :: (a -> ST s a) -> ST s a
-fixST m = ST (\ s ->
- let
+fixST m = ST (\ s ->
+ let
q@(r,_s') = unST (m r) s
in q)
-- Why don't we need unsafePerformIO in fixST? We create a thunk, q,
@@ -233,7 +232,7 @@ strictToLazyST (GHC.ST.ST m) = ST $ \(S# s) ->
(# s', a #) -> (a, S# s')
-- See Note [Lazy ST: not producing lazy pairs]
-{-|
+{-|
Convert a lazy 'ST' computation into a strict one.
-}
lazyToStrictST :: ST s a -> ST.ST s a
=====================================
libraries/base/GHC/IO/Encoding.hs
=====================================
@@ -107,6 +107,7 @@ utf32be = UTF32.utf32be
--
-- @since 4.5.0.0
getLocaleEncoding :: IO TextEncoding
+{-# NOINLINE getLocaleEncoding #-}
-- | The Unicode encoding of the current locale, but allowing arbitrary
-- undecodable bytes to be round-tripped through it.
@@ -120,6 +121,7 @@ getLocaleEncoding :: IO TextEncoding
--
-- @since 4.5.0.0
getFileSystemEncoding :: IO TextEncoding
+{-# NOINLINE getFileSystemEncoding #-}
-- | The Unicode encoding of the current locale, but where undecodable
-- bytes are replaced with their closest visual match. Used for
@@ -127,9 +129,13 @@ getFileSystemEncoding :: IO TextEncoding
--
-- @since 4.5.0.0
getForeignEncoding :: IO TextEncoding
+{-# NOINLINE getForeignEncoding #-}
-- | @since 4.5.0.0
setLocaleEncoding, setFileSystemEncoding, setForeignEncoding :: TextEncoding -> IO ()
+{-# NOINLINE setLocaleEncoding #-}
+{-# NOINLINE setFileSystemEncoding #-}
+{-# NOINLINE setForeignEncoding #-}
(getLocaleEncoding, setLocaleEncoding) = mkGlobal initLocaleEncoding
(getFileSystemEncoding, setFileSystemEncoding) = mkGlobal initFileSystemEncoding
@@ -139,9 +145,13 @@ mkGlobal :: a -> (IO a, a -> IO ())
mkGlobal x = unsafePerformIO $ do
x_ref <- newIORef x
return (readIORef x_ref, writeIORef x_ref)
+{-# NOINLINE mkGlobal #-}
-- | @since 4.5.0.0
initLocaleEncoding, initFileSystemEncoding, initForeignEncoding :: TextEncoding
+{-# NOINLINE initLocaleEncoding #-}
+-- N.B. initLocaleEncoding is exported for use in System.IO.localeEncoding.
+-- NOINLINE ensures that this result is shared.
#if !defined(mingw32_HOST_OS)
-- It is rather important that we don't just call Iconv.mkIconvEncoding here
=====================================
libraries/base/GHC/ST.hs
=====================================
@@ -26,7 +26,7 @@ module GHC.ST (
import GHC.Base
import GHC.Show
-import qualified Control.Monad.Fail as Fail
+import Control.Monad.Fail
default ()
@@ -79,7 +79,7 @@ instance Monad (ST s) where
(k2 new_s) }})
-- | @since 4.11.0.0
-instance Fail.MonadFail (ST s) where
+instance MonadFail (ST s) where
fail s = errorWithoutStackTrace s
-- | @since 4.11.0.0
=====================================
libraries/base/Text/ParserCombinators/ReadPrec.hs
=====================================
@@ -64,7 +64,7 @@ import qualified Text.ParserCombinators.ReadP as ReadP
import GHC.Num( Num(..) )
import GHC.Base
-import qualified Control.Monad.Fail as MonadFail
+import Control.Monad.Fail
-- ---------------------------------------------------------------------------
-- The readPrec type
@@ -88,8 +88,8 @@ instance Monad ReadPrec where
P f >>= k = P (\n -> do a <- f n; let P f' = k a in f' n)
-- | @since 4.9.0.0
-instance MonadFail.MonadFail ReadPrec where
- fail s = P (\_ -> MonadFail.fail s)
+instance MonadFail ReadPrec where
+ fail s = P (\_ -> fail s)
-- | @since 2.01
instance MonadPlus ReadPrec
=====================================
libraries/ghci/GHCi/TH.hs
=====================================
@@ -97,7 +97,6 @@ import GHCi.RemoteTypes
import GHC.Serialized
import Control.Exception
-import qualified Control.Monad.Fail as Fail
import Control.Monad.IO.Class (MonadIO (..))
import Data.Binary
import Data.Binary.Put
@@ -144,11 +143,8 @@ instance Monad GHCiQ where
do (m', s') <- runGHCiQ m s
(a, s'') <- runGHCiQ (f m') s'
return (a, s'')
-#if !MIN_VERSION_base(4,13,0)
- fail = Fail.fail
-#endif
-instance Fail.MonadFail GHCiQ where
+instance MonadFail GHCiQ where
fail err = GHCiQ $ \s -> throwIO (GHCiQException s err)
getState :: GHCiQ QState
=====================================
libraries/integer-gmp/changelog.md
=====================================
@@ -1,5 +1,11 @@
# Changelog for [`integer-gmp` package](http://hackage.haskell.org/package/integer-gmp)
+## 1.0.3.0 *January 2019*
+
+ * Bundled with GHC 8.10.1
+
+ * Documentation changes
+
## 1.0.2.0 *April 2018*
* Bundled with GHC 8.4.2
=====================================
libraries/integer-gmp/integer-gmp.cabal
=====================================
@@ -1,6 +1,6 @@
cabal-version: 2.0
name: integer-gmp
-version: 1.0.2.0
+version: 1.0.3.0
synopsis: Integer library based on GMP
license: BSD3
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -52,15 +52,13 @@ import Numeric.Natural
import Prelude
import Foreign.ForeignPtr
-import qualified Control.Monad.Fail as Fail
-
-----------------------------------------------------
--
-- The Quasi class
--
-----------------------------------------------------
-class (MonadIO m, Fail.MonadFail m) => Quasi m where
+class (MonadIO m, MonadFail m) => Quasi m where
qNewName :: String -> m Name
-- ^ Fresh names
@@ -187,12 +185,9 @@ runQ (Q m) = m
instance Monad Q where
Q m >>= k = Q (m >>= \x -> unQ (k x))
(>>) = (*>)
-#if !MIN_VERSION_base(4,13,0)
- fail = Fail.fail
-#endif
-instance Fail.MonadFail Q where
- fail s = report True s >> Q (Fail.fail "Q monad failure")
+instance MonadFail Q where
+ fail s = report True s >> Q (fail "Q monad failure")
instance Functor Q where
fmap f (Q x) = Q (fmap f x)
=====================================
testsuite/tests/perf/should_run/all.T
=====================================
@@ -233,8 +233,7 @@ test('T5949',
['-O'])
test('T4267',
- [expect_broken(4267),
- collect_stats('bytes allocated',10),
+ [collect_stats('bytes allocated',10),
only_ways(['normal'])],
compile_and_run,
['-O'])
=====================================
testsuite/tests/polykinds/T17963.hs
=====================================
@@ -0,0 +1,15 @@
+{-# Language DataKinds #-}
+{-# Language PolyKinds #-}
+{-# Language RankNTypes #-}
+{-# Language StandaloneKindSignatures #-}
+{-# Language TypeApplications #-}
+module T17963 where
+
+import GHC.Types (Constraint, Type, TYPE, RuntimeRep(..))
+
+type Cat :: forall (rep :: RuntimeRep). TYPE rep -> Type
+type Cat ob = ob -> ob -> Type
+
+type Category' :: forall rep (ob :: TYPE rep). Cat @rep ob -> Constraint
+class Category' (cat :: Cat @rep ob) where
+ id' :: forall a. cat a a
=====================================
testsuite/tests/polykinds/T17963.stderr
=====================================
@@ -0,0 +1,13 @@
+
+T17963.hs:15:23: error:
+ • Couldn't match a lifted type with an unlifted type
+ ‘rep1’ is a rigid type variable bound by
+ the class declaration for ‘Category'’
+ at T17963.hs:13:27-29
+ When matching kinds
+ k0 :: *
+ ob :: TYPE rep1
+ Expected kind ‘ob’, but ‘a’ has kind ‘k0’
+ • In the first argument of ‘cat’, namely ‘a’
+ In the type signature: id' :: forall a. cat a a
+ In the class declaration for ‘Category'’
=====================================
testsuite/tests/polykinds/all.T
=====================================
@@ -216,3 +216,4 @@ test('T16263', normal, compile_fail, [''])
test('T16902', normal, compile_fail, [''])
test('CuskFam', normal, compile, [''])
test('T17841', normal, compile_fail, [''])
+test('T17963', normal, compile_fail, [''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/636bf8ad7280623bdb2d0f9b49168af9290b406f...de7bfdb12f665a7a7dcc49f42db9d3f2c895e148
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/636bf8ad7280623bdb2d0f9b49168af9290b406f...de7bfdb12f665a7a7dcc49f42db9d3f2c895e148
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/20200331/9073d705/attachment-0001.html>
More information about the ghc-commits
mailing list