[commit: ghc] wip/spj-wildcard-refactor: Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor (d5d2338)

git at git.haskell.org git at git.haskell.org
Tue Dec 1 12:59:35 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/spj-wildcard-refactor
Link       : http://ghc.haskell.org/trac/ghc/changeset/d5d233848a527b93f1acf386666da0d2b545a307/ghc

>---------------------------------------------------------------

commit d5d233848a527b93f1acf386666da0d2b545a307
Merge: 0c60c0e 290def7
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Nov 30 14:10:58 2015 +0000

    Merge remote-tracking branch 'origin/master' into wip/spj-wildcard-refactor
    
    Conflicts:
    	compiler/hsSyn/HsTypes.hs
    	compiler/rename/RnSplice.hs
    	testsuite/tests/ghci/scripts/T10248.stderr
    	testsuite/tests/typecheck/should_fail/CustomTypeErrors02.stderr
    	testsuite/tests/wcompat-warnings/WCompatWarningsOn.stderr



>---------------------------------------------------------------

d5d233848a527b93f1acf386666da0d2b545a307
 compiler/hsSyn/HsTypes.hs                          |  16 ++
 compiler/llvmGen/LlvmCodeGen/CodeGen.hs            |  10 ++
 compiler/main/DynFlags.hs                          |  33 +++-
 compiler/main/Packages.hs                          |  16 ++
 compiler/parser/Lexer.x                            |  26 +--
 compiler/prelude/PrelNames.hs                      |  29 ++-
 compiler/rename/RnSplice.hs                        |  28 +--
 compiler/simplCore/CoreMonad.hs                    |   2 +-
 compiler/simplCore/SimplCore.hs                    |   9 +-
 compiler/typecheck/TcErrors.hs                     |   9 +
 compiler/typecheck/TcRnDriver.hs                   | 196 ++++++++++++++++++++-
 compiler/typecheck/TcTyClsDecls.hs                 |  23 ++-
 compiler/utils/OrdList.hs                          |   9 +
 compiler/utils/UniqFM.hs                           |   9 +
 docs/users_guide/7.12.1-notes.rst                  |  16 +-
 docs/users_guide/glasgow_exts.rst                  |  13 +-
 docs/users_guide/using-warnings.rst                |  18 +-
 ghc/GhciMonad.hs                                   |  14 +-
 ghc/InteractiveUI.hs                               | 167 +++++++++++-------
 libraries/base/GHC/ExecutionStack.hs               |   5 +-
 libraries/base/GHC/ExecutionStack/Internal.hsc     |  14 +-
 libraries/base/Text/ParserCombinators/ReadP.hs     |   7 -
 libraries/base/Text/ParserCombinators/ReadPrec.hs  |   5 -
 rts/LibdwPool.c                                    |  19 +-
 rts/Pool.c                                         |  41 +++--
 rts/Pool.h                                         |  10 +-
 testsuite/tests/cabal/cabal07/cabal07.stderr       |   2 +-
 testsuite/tests/driver/T10970.stdout               |   2 +-
 testsuite/tests/driver/T4437.hs                    |   1 +
 testsuite/tests/ghci/scripts/T10248.stderr         |   0
 .../tests/indexed-types/should_fail/T11136.hs      |   7 +
 .../tests/indexed-types/should_fail/T11136.stderr  |   5 +
 testsuite/tests/indexed-types/should_fail/all.T    |   1 +
 testsuite/tests/package/package01e.stderr          |   4 +-
 testsuite/tests/quasiquotation/qq008/Test.hs       |   2 +-
 testsuite/tests/quasiquotation/qq008/qq008.stderr  |   4 -
 testsuite/tests/quotes/T10384.hs                   |   2 +-
 testsuite/tests/quotes/all.T                       |   2 +-
 .../safeHaskell/safeLanguage/SafeLang12.stderr     |  11 +-
 testsuite/tests/{ado => semigroup}/Makefile        |   0
 testsuite/tests/semigroup/SemigroupWarnings.hs     |  34 ++++
 testsuite/tests/semigroup/SemigroupWarnings.stderr |   8 +
 testsuite/tests/semigroup/all.T                    |   1 +
 .../should_fail/CustomTypeErrors02.stderr          |   4 +-
 .../tests/wcompat-warnings/WCompatWarningsNotOn.hs |   2 +
 .../tests/wcompat-warnings/WCompatWarningsOff.hs   |   2 +
 .../tests/wcompat-warnings/WCompatWarningsOn.hs    |   2 +
 .../wcompat-warnings/WCompatWarningsOn.stderr      |   6 +-
 .../tests/wcompat-warnings/WCompatWarningsOnOff.hs |   2 +
 utils/ghc-pkg/Main.hs                              |   2 +
 utils/mkUserGuidePart/Options/Language.hs          |   7 +
 utils/mkUserGuidePart/Options/Warnings.hs          |  11 +-
 52 files changed, 681 insertions(+), 187 deletions(-)

diff --cc compiler/hsSyn/HsTypes.hs
index 9134f39,eda643c..228df71
--- a/compiler/hsSyn/HsTypes.hs
+++ b/compiler/hsSyn/HsTypes.hs
@@@ -87,6 -86,13 +87,13 @@@ import Maybes( isJust 
  
  import Data.Data hiding ( Fixity )
  import Data.Maybe ( fromMaybe )
+ #if __GLASGOW_HASKELL__ < 709
 -import Data.Monoid hiding ((<>))
++import Data.Monoid hiding((<>))
+ #endif
 -#if __GLASGOW_HASKELL__ > 710
++#if __GLASGOW_HASKELL > 710
+ import Data.Semigroup   ( Semigroup )
+ import qualified Data.Semigroup as Semigroup
+ #endif
  
  {-
  ************************************************************************
@@@ -205,17 -164,34 +212,26 @@@ data LHsQTyVars name   -- See Note [HsT
               -- See Note [HsForAllTy tyvar binders]
      }
    deriving( Typeable )
 -deriving instance (DataId name) => Data (LHsTyVarBndrs name)
  
 -mkHsQTvs :: [LHsTyVarBndr RdrName] -> LHsTyVarBndrs RdrName
 --- Just at RdrName because in the Name variant we should know just
 --- what the kind-variable binders are; and we don't
 --- We put an empty list (rather than a panic) for the kind vars so
 --- that the pretty printer works ok on them.
 -mkHsQTvs tvs = HsQTvs { hsq_kvs = [], hsq_tvs = tvs }
 +deriving instance (DataId name) => Data (LHsQTyVars name)
  
 -emptyHsQTvs :: LHsTyVarBndrs name   -- Use only when you know there are no kind binders
 -emptyHsQTvs =  HsQTvs { hsq_kvs = [], hsq_tvs = [] }
 +mkHsQTvs :: [LHsTyVarBndr RdrName] -> LHsQTyVars RdrName
 +mkHsQTvs tvs = HsQTvs { hsq_kvs = PlaceHolder, hsq_tvs = tvs }
  
 -hsQTvBndrs :: LHsTyVarBndrs name -> [LHsTyVarBndr name]
 +hsQTvBndrs :: LHsQTyVars name -> [LHsTyVarBndr name]
  hsQTvBndrs = hsq_tvs
  
 -#if __GLASGOW_HASKELL__ > 710
+ instance Semigroup (LHsTyVarBndrs name) where
+   HsQTvs kvs1 tvs1 <> HsQTvs kvs2 tvs2
+     = HsQTvs (kvs1 ++ kvs2) (tvs1 ++ tvs2)
 -#endif
+ 
+ instance Monoid (LHsTyVarBndrs name) where
+   mempty = emptyHsQTvs
+   mappend (HsQTvs kvs1 tvs1) (HsQTvs kvs2 tvs2)
+     = HsQTvs (kvs1 ++ kvs2) (tvs1 ++ tvs2)
+ 
  ------------------------------------------------
 ---            HsWithBndrs
 +--            HsImplicitBndrs
  -- Used to quantify the binders of a type in cases
  -- when a HsForAll isn't appropriate:
  --    * Patterns in a type/data family instance (HsTyPats)
diff --cc compiler/rename/RnSplice.hs
index 8c84e3d,2093312..3c7695b
--- a/compiler/rename/RnSplice.hs
+++ b/compiler/rename/RnSplice.hs
@@@ -44,7 -45,7 +44,6 @@@ import Hook
  import Var              ( Id )
  import THNames          ( quoteExpName, quotePatName, quoteDecName, quoteTypeName
                          , decsQTyConName, expQTyConName, patQTyConName, typeQTyConName, )
- import Util
 -import RnTypes          ( collectWildCards )
  
  import {-# SOURCE #-} TcExpr   ( tcMonoExpr )
  import {-# SOURCE #-} TcSplice ( runMetaD, runMetaE, runMetaP, runMetaT, tcTopSpliceExpr )



More information about the ghc-commits mailing list